Skip to content

Commit

Permalink
[Site] Add the search path in library not found error
Browse files Browse the repository at this point in the history
Signed-off-by: François Bobot <[email protected]>
  • Loading branch information
bobot committed Nov 17, 2021
1 parent c6854af commit 10870a1
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 16 deletions.
33 changes: 20 additions & 13 deletions otherlibs/site/src/plugins/plugins.ml
Original file line number Diff line number Diff line change
Expand Up @@ -67,19 +67,23 @@ let rec get_plugin plugins requires entries =
get_plugin plugins (value :: requires) entries
| Rule _ :: entries -> get_plugin plugins requires entries

exception Library_not_found of string
exception Library_not_found of string list * string

exception Plugin_not_found of string list * string

let () =
Printexc.register_printer (function
| Plugin_not_found (paths, name) ->
Some
(Format.sprintf "The plugin is %s absent in the paths [%s]" name
(Format.sprintf "The plugin %S can't be found in the paths [%s]" name
(String.concat ";" paths))
| Library_not_found (paths, name) ->
Some
(Format.sprintf "The library %S can't be found in the paths [%s]" name
(String.concat ";" paths))
| _ -> None)

let rec find_library ~suffix directory meta =
let rec find_library ~dirs ~suffix directory meta =
let rec find_directory directory = function
| [] -> directory
| Meta_parser.Rule
Expand All @@ -95,10 +99,10 @@ let rec find_library ~suffix directory meta =
| pkg :: suffix ->
let directory = find_directory directory meta in
let rec aux pkg = function
| [] -> raise (Library_not_found pkg)
| [] -> raise (Library_not_found (dirs, pkg))
| Meta_parser.Package { name = Some name; entries } :: _
when String.equal name pkg ->
find_library ~suffix directory entries
find_library ~dirs ~suffix directory entries
| _ :: entries -> aux pkg entries
in
aux pkg meta
Expand Down Expand Up @@ -132,8 +136,10 @@ let extract_comma_space_separated_words s =

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

let find_plugin ~dir ~suffix meta =
let directory, meta = find_library ~suffix None meta.Meta_parser.entries in
let find_plugin ~dirs ~dir ~suffix meta =
let directory, meta =
find_library ~dirs ~suffix None meta.Meta_parser.entries
in
let plugins, requires = get_plugin [] [] meta in
let directory =
match directory with
Expand Down Expand Up @@ -184,24 +190,25 @@ let lookup_and_load_one_dir ~dir ~pkg =
else
None

let split name =
let split ~dirs name =
match String.split_on_char '.' name with
| [] -> raise (Library_not_found name)
| [] -> raise (Library_not_found (dirs, name))
| pkg :: rest -> (pkg, rest)

let lookup_and_summarize dirs name =
let pkg, suffix = split name in
let pkg, suffix = split ~dirs name in
let rec loop dirs =
match dirs with
| [] -> (
List.assoc_opt pkg Data.builtin_library |> function
| None -> raise (Library_not_found name)
| Some meta -> find_plugin ~dir:(Lazy.force Helpers.stdlib) ~suffix meta)
| None -> raise (Library_not_found (dirs, name))
| Some meta ->
find_plugin ~dirs ~dir:(Lazy.force Helpers.stdlib) ~suffix meta)
| dir :: dirs -> (
let dir = Filename.concat dir pkg in
match lookup_and_load_one_dir ~dir ~pkg with
| None -> loop dirs
| Some p -> find_plugin ~dir ~suffix p)
| Some p -> find_plugin ~dirs ~dir ~suffix p)
in
loop dirs

Expand Down
20 changes: 17 additions & 3 deletions otherlibs/site/test/plugin_with_dot.t
Original file line number Diff line number Diff line change
Expand Up @@ -49,15 +49,15 @@
> (rule
> (targets out.log)
> (deps (package c))
> (action (with-stdout-to out.log (run %{bin:c}))))
> (action (with-stdout-to out.log (run %{bin:c} "c-plugins-b.b"))))
> EOF

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

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

Expand All @@ -72,6 +72,20 @@ Build everything

Test with dune exec
--------------------------------
$ dune exec -- c/c.exe
$ dune exec -- c/c.exe "c-plugins-b.b"
run b
run c: registered:b.

Test error messages
--------------------------------
$ dune exec -- c/c.exe "inexistent"
Fatal error: exception The plugin "inexistent" can't be found in the paths [$TESTCASE_ROOT/_build/install/default/lib/c/plugins]
[2]

$ cat >c/c.ml <<EOF
> let () = Dune_site_plugins.V1.load Sys.argv.(1)
> EOF

$ dune exec -- c/c.exe "inexistent"
Fatal error: exception The library "inexistent" can't be found in the paths []
[2]

0 comments on commit 10870a1

Please sign in to comment.