@@ -67,19 +67,23 @@ let rec get_plugin plugins requires entries =
67
67
get_plugin plugins (value :: requires) entries
68
68
| Rule _ :: entries -> get_plugin plugins requires entries
69
69
70
- exception Library_not_found of string
70
+ exception Library_not_found of string list * string
71
71
72
72
exception Plugin_not_found of string list * string
73
73
74
74
let () =
75
75
Printexc. register_printer (function
76
76
| Plugin_not_found (paths , name ) ->
77
77
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
79
83
(String. concat " ;" paths))
80
84
| _ -> None )
81
85
82
- let rec find_library ~suffix directory meta =
86
+ let rec find_library ~dirs ~ suffix directory meta =
83
87
let rec find_directory directory = function
84
88
| [] -> directory
85
89
| Meta_parser. Rule
@@ -95,10 +99,10 @@ let rec find_library ~suffix directory meta =
95
99
| pkg :: suffix ->
96
100
let directory = find_directory directory meta in
97
101
let rec aux pkg = function
98
- | [] -> raise (Library_not_found pkg)
102
+ | [] -> raise (Library_not_found (dirs, pkg) )
99
103
| Meta_parser. Package { name = Some name; entries } :: _
100
104
when String. equal name pkg ->
101
- find_library ~suffix directory entries
105
+ find_library ~dirs ~ suffix directory entries
102
106
| _ :: entries -> aux pkg entries
103
107
in
104
108
aux pkg meta
@@ -132,8 +136,10 @@ let extract_comma_space_separated_words s =
132
136
133
137
let split_all l = List. concat (List. map extract_comma_space_separated_words l)
134
138
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
137
143
let plugins, requires = get_plugin [] [] meta in
138
144
let directory =
139
145
match directory with
@@ -184,24 +190,25 @@ let lookup_and_load_one_dir ~dir ~pkg =
184
190
else
185
191
None
186
192
187
- let split name =
193
+ let split ~ dirs name =
188
194
match String. split_on_char '.' name with
189
- | [] -> raise (Library_not_found name)
195
+ | [] -> raise (Library_not_found (dirs, name) )
190
196
| pkg :: rest -> (pkg, rest)
191
197
192
198
let lookup_and_summarize dirs name =
193
- let pkg, suffix = split name in
199
+ let pkg, suffix = split ~dirs name in
194
200
let rec loop dirs =
195
201
match dirs with
196
202
| [] -> (
197
203
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)
200
207
| dir :: dirs -> (
201
208
let dir = Filename. concat dir pkg in
202
209
match lookup_and_load_one_dir ~dir ~pkg with
203
210
| None -> loop dirs
204
- | Some p -> find_plugin ~dir ~suffix p)
211
+ | Some p -> find_plugin ~dirs ~ dir ~suffix p)
205
212
in
206
213
loop dirs
207
214
0 commit comments