Skip to content

Commit d35dc3d

Browse files
committed
[Site] Add the search path in library not found error
Signed-off-by: François Bobot <francois.bobot@cea.fr>
1 parent 76d5119 commit d35dc3d

File tree

2 files changed

+37
-16
lines changed

2 files changed

+37
-16
lines changed

otherlibs/site/src/plugins/plugins.ml

+20-13
Original file line numberDiff line numberDiff line change
@@ -67,19 +67,23 @@ let rec get_plugin plugins requires entries =
6767
get_plugin plugins (value :: requires) entries
6868
| Rule _ :: entries -> get_plugin plugins requires entries
6969

70-
exception Library_not_found of string
70+
exception Library_not_found of string list * string
7171

7272
exception Plugin_not_found of string list * string
7373

7474
let () =
7575
Printexc.register_printer (function
7676
| Plugin_not_found (paths, name) ->
7777
Some
78-
(Format.sprintf "The plugin is %s absent in the paths [%s]" name
78+
(Format.sprintf "The plugin %S can't be found in the paths [%s]" name
79+
(String.concat ";" paths))
80+
| Library_not_found (paths, name) ->
81+
Some
82+
(Format.sprintf "The library %S can't be found in the paths [%s]" name
7983
(String.concat ";" paths))
8084
| _ -> None)
8185

82-
let rec find_library ~suffix directory meta =
86+
let rec find_library ~dirs ~suffix directory meta =
8387
let rec find_directory directory = function
8488
| [] -> directory
8589
| Meta_parser.Rule
@@ -95,10 +99,10 @@ let rec find_library ~suffix directory meta =
9599
| pkg :: suffix ->
96100
let directory = find_directory directory meta in
97101
let rec aux pkg = function
98-
| [] -> raise (Library_not_found pkg)
102+
| [] -> raise (Library_not_found (dirs, pkg))
99103
| Meta_parser.Package { name = Some name; entries } :: _
100104
when String.equal name pkg ->
101-
find_library ~suffix directory entries
105+
find_library ~dirs ~suffix directory entries
102106
| _ :: entries -> aux pkg entries
103107
in
104108
aux pkg meta
@@ -132,8 +136,10 @@ let extract_comma_space_separated_words s =
132136

133137
let split_all l = List.concat (List.map extract_comma_space_separated_words l)
134138

135-
let find_plugin ~dir ~suffix meta =
136-
let directory, meta = find_library ~suffix None meta.Meta_parser.entries in
139+
let find_plugin ~dirs ~dir ~suffix meta =
140+
let directory, meta =
141+
find_library ~dirs ~suffix None meta.Meta_parser.entries
142+
in
137143
let plugins, requires = get_plugin [] [] meta in
138144
let directory =
139145
match directory with
@@ -184,24 +190,25 @@ let lookup_and_load_one_dir ~dir ~pkg =
184190
else
185191
None
186192

187-
let split name =
193+
let split ~dirs name =
188194
match String.split_on_char '.' name with
189-
| [] -> raise (Library_not_found name)
195+
| [] -> raise (Library_not_found (dirs, name))
190196
| pkg :: rest -> (pkg, rest)
191197

192198
let lookup_and_summarize dirs name =
193-
let pkg, suffix = split name in
199+
let pkg, suffix = split ~dirs name in
194200
let rec loop dirs =
195201
match dirs with
196202
| [] -> (
197203
List.assoc_opt pkg Data.builtin_library |> function
198-
| None -> raise (Library_not_found name)
199-
| Some meta -> find_plugin ~dir:(Lazy.force Helpers.stdlib) ~suffix meta)
204+
| None -> raise (Library_not_found (dirs, name))
205+
| Some meta ->
206+
find_plugin ~dirs ~dir:(Lazy.force Helpers.stdlib) ~suffix meta)
200207
| dir :: dirs -> (
201208
let dir = Filename.concat dir pkg in
202209
match lookup_and_load_one_dir ~dir ~pkg with
203210
| None -> loop dirs
204-
| Some p -> find_plugin ~dir ~suffix p)
211+
| Some p -> find_plugin ~dirs ~dir ~suffix p)
205212
in
206213
loop dirs
207214

otherlibs/site/test/plugin_with_dot.t

+17-3
Original file line numberDiff line numberDiff line change
@@ -49,15 +49,15 @@
4949
> (rule
5050
> (targets out.log)
5151
> (deps (package c))
52-
> (action (with-stdout-to out.log (run %{bin:c}))))
52+
> (action (with-stdout-to out.log (run %{bin:c} "c-plugins-b.b"))))
5353
> EOF
5454

5555
$ cat >c/c_register.ml <<EOF
5656
> let registered : string list ref = ref []
5757
> EOF
5858

5959
$ cat >c/c.ml <<EOF
60-
> let () = Sites.Plugins.Plugins.load "c-plugins-b.b"
60+
> let () = Sites.Plugins.Plugins.load Sys.argv.(1)
6161
> let () = Printf.printf "run c: registered:%s.\n%!" (String.concat "," !C_register.registered)
6262
> EOF
6363

@@ -72,6 +72,20 @@ Build everything
7272

7373
Test with dune exec
7474
--------------------------------
75-
$ dune exec -- c/c.exe
75+
$ dune exec -- c/c.exe "c-plugins-b.b"
7676
run b
7777
run c: registered:b.
78+
79+
Test error messages
80+
--------------------------------
81+
$ 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]
84+
85+
$ cat >c/c.ml <<EOF
86+
> let () = Dune_site_plugins.V1.load Sys.argv.(1)
87+
> EOF
88+
89+
$ dune exec -- c/c.exe "inexistent"
90+
Fatal error: exception The library "inexistent" can't be found in the paths []
91+
[2]

0 commit comments

Comments
 (0)