Skip to content

Commit

Permalink
Integrate simplified json index output
Browse files Browse the repository at this point in the history
  • Loading branch information
jonludlam committed Jan 22, 2025
1 parent f0dba28 commit 900ace0
Show file tree
Hide file tree
Showing 7 changed files with 23 additions and 8 deletions.
4 changes: 2 additions & 2 deletions src/driver/bin/odoc_driver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,8 +71,8 @@ let run_inner ~odoc_dir ~odocl_dir ~index_dir ~mld_dir ~compile_grep ~link_grep
output
in
let () =
Compile.html_generate ~occurrence_file ~remaps ~generate_json html_dir
linked
Compile.html_generate ~occurrence_file ~remaps ~generate_json
~simplified_search_output:false html_dir linked
in
let _ = Odoc.support_files html_dir in
Stats.stats.finished <- true;
Expand Down
2 changes: 1 addition & 1 deletion src/driver/bin/odoc_driver_monorepo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ let run path extra_pkgs extra_libs
in
let () =
Compile.html_generate ~occurrence_file ~remaps:[] ~generate_json
html_dir linked
~simplified_search_output:false html_dir linked
in
let _ = Odoc.support_files html_dir in
Stats.stats.finished <- true;
Expand Down
2 changes: 1 addition & 1 deletion src/driver/bin/odoc_driver_voodoo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ let run package_name blessed actions odoc_dir odocl_dir
in
let () =
Compile.html_generate ~occurrence_file ~remaps:[] ~generate_json
html_dir linked
~simplified_search_output:true html_dir linked
in
let _ = Odoc.support_files html_dir in
()
Expand Down
11 changes: 9 additions & 2 deletions src/driver/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -282,7 +282,8 @@ let sherlodoc_index_one ~output_dir (index : Odoc_unit.index) =
Sherlodoc.index ~format:`js ~inputs ~dst ();
rel_path

let html_generate ~occurrence_file ~remaps ~generate_json output_dir linked =
let html_generate ~occurrence_file ~remaps ~generate_json
~simplified_search_output output_dir linked =
let tbl = Hashtbl.create 10 in
let _ = OS.Dir.create output_dir |> Result.get_ok in
Sherlodoc.js Fpath.(output_dir // Sherlodoc.js_file);
Expand All @@ -292,7 +293,8 @@ let html_generate ~occurrence_file ~remaps ~generate_json output_dir linked =
({ roots; output_file; json; search_dir = _; sidebar } as index :
Odoc_unit.index) =
let () =
Odoc.compile_index ~json ~occurrence_file ~output_file ~roots ()
Odoc.compile_index ~json ~occurrence_file ~output_file ~roots
~simplified:false ~wrap:false ()
in
let sidebar =
match sidebar with
Expand All @@ -302,6 +304,11 @@ let html_generate ~occurrence_file ~remaps ~generate_json output_dir linked =
Odoc.sidebar_generate
~output_file:Fpath.(output_dir // pkg_dir / "sidebar.json")
~json:true index.output_file ();
if simplified_search_output then
Odoc.compile_index ~json:true ~occurrence_file
~output_file:Fpath.(output_dir // pkg_dir / "index.js")
~simplified:true ~wrap:true ~roots ();

Some output_file
in
(sherlodoc_index_one ~output_dir index, sidebar)
Expand Down
1 change: 1 addition & 0 deletions src/driver/compile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ val html_generate :
occurrence_file:Fpath.t ->
remaps:(string * string) list ->
generate_json:bool ->
simplified_search_output:bool ->
Fpath.t ->
linked list ->
unit
9 changes: 7 additions & 2 deletions src/driver/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -168,19 +168,24 @@ let link ?(ignore_output = false) ~custom_layout ~input_file:file ?output_file
ignore @@ Cmd_outputs.submit log desc cmd (Some output_file)

let compile_index ?(ignore_output = false) ~output_file ?occurrence_file ~json
~roots () =
~roots ~simplified ~wrap () =
let roots =
List.fold_left (fun c r -> Cmd.(c % "--root" % p r)) Cmd.empty roots
in
let json = if json then Cmd.v "--json" else Cmd.empty in
let simplified =
if simplified then Cmd.v "--simplified-json" else Cmd.empty
in
let wrap = if wrap then Cmd.v "--wrap-json" else Cmd.empty in
let occ =
match occurrence_file with
| None -> Cmd.empty
| Some f -> Cmd.(v "--occurrences" % p f)
in
let cmd =
Cmd.(
!odoc % "compile-index" %% json %% v "-o" % p output_file %% roots %% occ)
!odoc % "compile-index" %% json %% simplified %% wrap %% v "-o"
% p output_file %% roots %% occ)
in
let desc =
Printf.sprintf "Generating index for %s" (Fpath.to_string output_file)
Expand Down
2 changes: 2 additions & 0 deletions src/driver/odoc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,8 @@ val compile_index :
?occurrence_file:Fpath.t ->
json:bool ->
roots:Fpath.t list ->
simplified:bool ->
wrap:bool ->
unit ->
unit

Expand Down

0 comments on commit 900ace0

Please sign in to comment.