Skip to content

Commit 138a570

Browse files
committed
Allow classify to run on multiple dirs
This is to help with classifying libraries in dune _build directories. In that case, the cmt{,i} files are in a separate directory than the archives.
1 parent 5367937 commit 138a570

File tree

2 files changed

+23
-22
lines changed

2 files changed

+23
-22
lines changed

src/odoc/bin/main.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1560,11 +1560,11 @@ module Odoc_error = struct
15601560
end
15611561

15621562
module Classify = struct
1563-
let libdir =
1564-
let doc = "The directory containing the libraries" in
1565-
Arg.(required & pos 0 (some string) None & info ~doc ~docv:"DIR" [])
1563+
let libdirs =
1564+
let doc = "The directories containing the libraries" in
1565+
Arg.(value & pos_all string [] & info ~doc ~docv:"DIR" [])
15661566

1567-
let cmd = Term.(const handle_error $ (const Classify.classify $ libdir))
1567+
let cmd = Term.(const handle_error $ (const Classify.classify $ libdirs))
15681568

15691569
let info ~docs =
15701570
Term.info "classify" ~docs

src/odoc/classify.cppo.ml

Lines changed: 19 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -192,13 +192,13 @@ let read_cmi ic =
192192

193193
#endif
194194

195-
let classify dir files libraries =
196-
let libraries = StringSet.elements libraries in
195+
let classify files libraries =
196+
let libraries = Fpath.Set.elements libraries in
197197

198198
let archives =
199199
List.map
200-
(fun lname ->
201-
let path ext = Fpath.(v dir / lname |> set_ext ext |> to_string) in
200+
(fun lpath ->
201+
let path ext = Fpath.(set_ext ext lpath |> to_string) in
202202
let paths = [ path ".cma"; path ".cmxa" ] in
203203
List.fold_left
204204
(fun cur path ->
@@ -210,20 +210,20 @@ let classify dir files libraries =
210210
| Error (`Msg m) ->
211211
Format.eprintf "Error reading library: %s\n%!" m;
212212
cur)
213-
(Archive.empty lname) paths)
213+
(Archive.empty (Fpath.basename lpath)) paths)
214214
libraries
215215
in
216216

217-
let cmis = List.filter (fun f -> Fpath.(has_ext ".cmi" (v f))) files in
217+
let cmis = List.filter (Fpath.has_ext ".cmi") files in
218218
let cmi_names =
219219
List.map
220-
(fun f -> Fpath.(rem_ext (v f) |> basename |> Astring.String.Ascii.capitalize))
220+
(fun f -> Fpath.(rem_ext f |> basename |> Astring.String.Ascii.capitalize))
221221
cmis
222222
in
223223

224224
let _impls, intfs =
225225
let check f ext =
226-
Sys.file_exists Fpath.(v dir / f |> set_ext ext |> to_string)
226+
Sys.file_exists Fpath.(set_ext ext f |> to_string)
227227
in
228228
List.partition (fun f -> check f ".cmo" || check f "cmx") cmis
229229
in
@@ -232,9 +232,9 @@ let classify dir files libraries =
232232
List.map
233233
(fun f ->
234234
let modname =
235-
Filename.chop_suffix f ".cmi" |> Astring.String.Ascii.capitalize
235+
Filename.chop_suffix (Fpath.basename f) ".cmi" |> Astring.String.Ascii.capitalize
236236
in
237-
(modname, Cmi.get_deps Fpath.(v dir / f |> to_string)))
237+
(modname, Cmi.get_deps Fpath.(f |> to_string)))
238238
intfs
239239
in
240240

@@ -398,18 +398,19 @@ let classify dir files libraries =
398398

399399
()
400400

401-
let classify dir =
402-
let files = Sys.readdir dir |> Array.to_list in
401+
let classify dirs =
402+
let files =
403+
List.map (fun dir ->
404+
Sys.readdir dir |> Array.to_list |> List.map (fun p -> Fpath.(v dir / p))) dirs |> List.flatten in
403405

404406
let libraries =
405407
List.fold_left
406-
(fun acc f ->
407-
let p = Fpath.v f in
408+
(fun acc p ->
408409
if Fpath.has_ext ".cma" p || Fpath.has_ext ".cmxa" p then
409-
StringSet.add Fpath.(rem_ext p |> to_string) acc
410+
Fpath.Set.add Fpath.(rem_ext p) acc
410411
else acc)
411-
StringSet.empty files
412+
Fpath.Set.empty files
412413
in
413414

414-
if StringSet.cardinal libraries = 0 then Ok ()
415-
else Ok (classify dir files libraries)
415+
if Fpath.Set.cardinal libraries = 0 then Ok ()
416+
else Ok (classify files libraries)

0 commit comments

Comments
 (0)