Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
21 changes: 19 additions & 2 deletions src/driver/bin/odoc_driver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -74,11 +74,28 @@ let run_inner ~odoc_dir ~odocl_dir ~index_dir ~mld_dir ~compile_grep ~link_grep
let linked =
Compile.link ~warnings_tags:packages ~custom_layout:false compiled
in
let odoc_dirs =
List.fold_left
(fun acc pkg ->
let lib_dirs =
List.map
(fun l -> Fpath.(odocl_dir // Odoc_unit.lib_dir pkg l))
pkg.libraries
in
Fpath.Set.union acc (Fpath.Set.of_list lib_dirs))
Fpath.Set.empty all
in

Logs.debug (fun m ->
m "odoc_dirs: %a" (Fmt.Dump.list Fpath.pp)
(Fpath.Set.to_list odoc_dirs));
let occurrence_file =
let output =
Fpath.( / ) odoc_dir "occurrences-all.odoc-occurrences"
Fpath.( / ) odocl_dir "occurrences-all.odoc-occurrences"
in
let () =
Odoc.count_occurrences ~input:(Fpath.Set.to_list odoc_dirs) ~output
in
let () = Odoc.count_occurrences ~input:[ odoc_dir ] ~output in
output
in
let () =
Expand Down
19 changes: 11 additions & 8 deletions src/driver/bin/odoc_driver_voodoo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,18 +54,24 @@ let run package_name blessed actions odoc_dir odocl_dir
Logs.set_reporter (Logs_fmt.reporter ());
Stats.init_nprocs nb_workers;
let () = Worker_pool.start_workers env sw nb_workers in
let odocl_dir = Option.value odocl_dir ~default:odoc_dir in

let all, extra_paths, actions, generate_json, occurrence_file =
let all, extra_paths, actions, generate_json, occurrence_file, odocl_dirs =
let pkg =
let pkg_opt = Voodoo.find_pkg package_name ~blessed in
match pkg_opt with Some pkg -> pkg | None -> exit 1
in
let all = Voodoo.of_voodoo pkg in
let odocl_dirs =
List.map
(fun l -> Fpath.(odocl_dir // Odoc_unit.lib_dir all l))
all.libraries
in
let occurrence_file =
Fpath.(odoc_dir // Voodoo.occurrence_file_of_pkg pkg)
Fpath.(odocl_dir // Voodoo.occurrence_file_of_pkg pkg)
in
let extra_paths = Voodoo.extra_paths odoc_dir in
(all, extra_paths, actions, true, occurrence_file)
(all, extra_paths, actions, true, occurrence_file, odocl_dirs)
in

let all = Packages.remap_virtual [ all ] in
Expand All @@ -78,10 +84,7 @@ let run package_name blessed actions odoc_dir odocl_dir
| _ -> failwith "Error, expecting singleton library in voodoo mode"
in
let units =
let dirs =
let odocl_dir = Option.value odocl_dir ~default:odoc_dir in
{ Odoc_unit.odoc_dir; odocl_dir; index_dir; mld_dir }
in
let dirs = { Odoc_unit.odoc_dir; odocl_dir; index_dir; mld_dir } in
Odoc_units_of.packages ~dirs ~indices_style:Voodoo ~extra_paths ~remap:false
all
in
Expand All @@ -101,7 +104,7 @@ let run package_name blessed actions odoc_dir odocl_dir
compiled
in
let () =
Odoc.count_occurrences ~input:[ odoc_dir ] ~output:occurrence_file
Odoc.count_occurrences ~input:odocl_dirs ~output:occurrence_file
in
let () =
Compile.html_generate ~occurrence_file ~remaps:[] ~generate_json
Expand Down
Loading