Skip to content

Commit 1096d61

Browse files
committed
[Plugin] Tidy error structure and message
Signed-off-by: François Bobot <[email protected]>
1 parent 0515b60 commit 1096d61

File tree

2 files changed

+68
-30
lines changed

2 files changed

+68
-30
lines changed

otherlibs/site/src/plugins/plugins.ml

Lines changed: 46 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -69,9 +69,18 @@ let rec get_plugin plugins requires entries =
6969

7070
exception Thread_library_required_by_plugin_but_not_required_by_main_executable
7171

72-
exception Library_not_found of string list * string
73-
74-
exception Plugin_not_found of string list * string
72+
exception
73+
Library_not_found of
74+
{ search_paths : string list
75+
; prefix : string list
76+
; name : string
77+
}
78+
79+
exception
80+
Plugin_not_found of
81+
{ search_paths : string list
82+
; name : string
83+
}
7584

7685
let () =
7786
Printexc.register_printer (function
@@ -81,17 +90,26 @@ let () =
8190
"It is not possible to dynamically link a plugin which uses the \
8291
thread library with an executable not already linked with the \
8392
thread library.")
84-
| Plugin_not_found (paths, name) ->
93+
| Plugin_not_found { search_paths; name } ->
94+
Some
95+
(Format.sprintf "The plugin %S can't be found in the search paths %S."
96+
name
97+
(String.concat ":" search_paths))
98+
| Library_not_found { search_paths; prefix = []; name } ->
8599
Some
86-
(Format.sprintf "The plugin %S can't be found in the paths [%s]" name
87-
(String.concat ";" paths))
88-
| Library_not_found (paths, name) ->
100+
(Format.sprintf "The library %S can't be found in the search paths %S."
101+
name
102+
(String.concat ":" search_paths))
103+
| Library_not_found { search_paths; prefix; name } ->
89104
Some
90-
(Format.sprintf "The library %S can't be found in the paths [%s]" name
91-
(String.concat ";" paths))
105+
(Format.sprintf
106+
"The sub-library %S can't be found in the library %s in the search \
107+
paths %S."
108+
name (String.concat "." prefix)
109+
(String.concat ":" search_paths))
92110
| _ -> None)
93111

94-
let rec find_library ~dirs ~suffix directory meta =
112+
let rec find_library ~dirs ~prefix ~suffix directory meta =
95113
let rec find_directory directory = function
96114
| [] -> directory
97115
| Meta_parser.Rule
@@ -107,10 +125,13 @@ let rec find_library ~dirs ~suffix directory meta =
107125
| pkg :: suffix ->
108126
let directory = find_directory directory meta in
109127
let rec aux pkg = function
110-
| [] -> raise (Library_not_found (dirs, pkg))
128+
| [] ->
129+
raise
130+
(Library_not_found
131+
{ search_paths = dirs; prefix = List.rev prefix; name = pkg })
111132
| Meta_parser.Package { name = Some name; entries } :: _
112133
when String.equal name pkg ->
113-
find_library ~dirs ~suffix directory entries
134+
find_library ~dirs ~prefix:(pkg :: prefix) ~suffix directory entries
114135
| _ :: entries -> aux pkg entries
115136
in
116137
aux pkg meta
@@ -144,9 +165,10 @@ let extract_comma_space_separated_words s =
144165

145166
let split_all l = List.concat (List.map extract_comma_space_separated_words l)
146167

147-
let find_plugin ~dirs ~dir ~suffix meta =
168+
let find_plugin ~dirs ~dir ~suffix (meta : Meta_parser.t) =
148169
let directory, meta =
149-
find_library ~dirs ~suffix None meta.Meta_parser.entries
170+
find_library ~dirs ~prefix:(Option.to_list meta.name) ~suffix None
171+
meta.entries
150172
in
151173
let plugins, requires = get_plugin [] [] meta in
152174
let directory =
@@ -200,25 +222,26 @@ let lookup_and_load_one_dir ~dir ~pkg =
200222

201223
let split ~dirs name =
202224
match String.split_on_char '.' name with
203-
| [] -> raise (Library_not_found (dirs, name))
225+
| [] -> raise (Library_not_found { search_paths = dirs; prefix = []; name })
204226
| pkg :: rest -> (pkg, rest)
205227

206-
let lookup_and_summarize dirs name =
207-
let pkg, suffix = split ~dirs name in
228+
let lookup_and_summarize alldirs name =
229+
let pkg, suffix = split ~dirs:alldirs name in
208230
let rec loop dirs =
209231
match dirs with
210232
| [] -> (
211233
List.assoc_opt pkg Data.builtin_library |> function
212-
| None -> raise (Library_not_found (dirs, name))
234+
| None ->
235+
raise (Library_not_found { search_paths = alldirs; prefix = []; name })
213236
| Some meta ->
214-
find_plugin ~dirs ~dir:(Lazy.force Helpers.stdlib) ~suffix meta)
237+
find_plugin ~dirs:alldirs ~dir:(Lazy.force Helpers.stdlib) ~suffix meta)
215238
| dir :: dirs -> (
216239
let dir = Filename.concat dir pkg in
217240
match lookup_and_load_one_dir ~dir ~pkg with
218241
| None -> loop dirs
219-
| Some p -> find_plugin ~dirs ~dir ~suffix p)
242+
| Some p -> find_plugin ~dirs:alldirs ~dir ~suffix p)
220243
in
221-
loop dirs
244+
loop alldirs
222245

223246
let loaded_libraries =
224247
lazy
@@ -247,10 +270,10 @@ let rec load_requires name =
247270

248271
let load_plugin plugin_paths name =
249272
match lookup plugin_paths (Filename.concat name meta_fn) with
250-
| None -> raise (Plugin_not_found (plugin_paths, name))
273+
| None -> raise (Plugin_not_found { search_paths = plugin_paths; name })
251274
| Some meta_file ->
252275
let meta = load meta_file ~pkg:name in
253-
let plugins, requires = get_plugin [] [] meta.Meta_parser.entries in
276+
let plugins, requires = get_plugin [] [] meta.entries in
254277
assert (plugins = []);
255278
let requires = split_all requires in
256279
List.iter load_requires requires

otherlibs/site/test/plugin_with_dot.t

Lines changed: 22 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,8 @@
5757
> EOF
5858

5959
$ cat >c/c.ml <<EOF
60-
> let () = Sites.Plugins.Plugins.load Sys.argv.(1)
60+
> let () = try Sites.Plugins.Plugins.load Sys.argv.(1)
61+
> with exn -> print_endline (Printexc.to_string exn)
6162
> let () = Printf.printf "run c: registered:%s.\n%!" (String.concat "," !C_register.registered)
6263
> EOF
6364

@@ -79,13 +80,27 @@ Test with dune exec
7980
Test error messages
8081
--------------------------------
8182
$ dune exec -- c/c.exe "inexistent"
82-
Fatal error: exception The plugin "inexistent" can't be found in the paths [$TESTCASE_ROOT/_build/install/default/lib/c/plugins]
83-
[2]
83+
The plugin "inexistent" can't be found in the search paths "$TESTCASE_ROOT/_build/install/default/lib/c/plugins".
84+
run c: registered:.
8485

8586
$ cat >c/c.ml <<EOF
86-
> let () = Dune_site_plugins.V1.load Sys.argv.(1)
87+
> let l = Lazy.force Dune_site.Private_.Helpers.ocamlpath
88+
> let l = List.map (Printf.sprintf "OCAMLPATH=%s") l
89+
> let () = print_string (String.concat ":" l)
8790
> EOF
8891

89-
$ dune exec -- c/c.exe "inexistent"
90-
Fatal error: exception The library "inexistent" can't be found in the paths []
91-
[2]
92+
$ export BUILD_PATH_PREFIX_MAP="$(dune exe -- c/c.exe):$BUILD_PATH_PREFIX_MAP"
93+
94+
$ cat >c/c.ml <<EOF
95+
> let () = try Dune_site_plugins.V1.load Sys.argv.(1)
96+
> with exn -> print_endline (Printexc.to_string exn)
97+
> EOF
98+
99+
$ dune exec -- c/c.exe "inexistent" 2>&1 | sed -e 's&default/lib:.*&default/lib:..."&g'
100+
The library "inexistent" can't be found in the search paths "$TESTCASE_ROOT/_build/install/default/lib:..."
101+
102+
$ dune exec -- c/c.exe "b.b.b"
103+
run b
104+
105+
$ dune exec -- c/c.exe "b.b.inexistent" 2>&1 | sed -e 's&default/lib:.*&default/lib:..."&g'
106+
The sub-library "inexistent" can't be found in the library b.b in the search paths "$TESTCASE_ROOT/_build/install/default/lib:..."

0 commit comments

Comments
 (0)