Skip to content

Commit

Permalink
WIP driver for generate index
Browse files Browse the repository at this point in the history
  • Loading branch information
EmileTrotignon committed Jun 4, 2024
1 parent 072efd9 commit 205afd9
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 0 deletions.
8 changes: 8 additions & 0 deletions src/driver/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -227,6 +227,14 @@ let link : compiled list -> _ =
in
Fiber.List.map link compiled |> List.concat

let index : linked list -> _ =
fun linked ->
let input_files =
linked |> List.map (fun l -> l.output_file) |> Fpath.Set.of_list
in
Odoc.compile_index ~marshall:true ~input_files ();
Odoc.compile_index ~marshall:false ~input_files ()

let html_generate : Fpath.t -> linked list -> _ =
fun output_dir linked ->
let html_generate : linked -> unit =
Expand Down
2 changes: 2 additions & 0 deletions src/driver/compile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,6 @@ type linked

val link : compiled list -> linked list

val index : linked list -> unit

val html_generate : Fpath.t -> linked list -> unit
21 changes: 21 additions & 0 deletions src/driver/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -116,6 +116,27 @@ let link ?(ignore_output = false) ~input_file:file ~includes ~docs ~libs () =
if not ignore_output then
add_prefixed_output cmd link_output (Fpath.to_string file) lines

let compile_index ?(ignore_output = false) ?dst ~marshall ~input_files ()=
let dst =
Fpath.v
@@
match dst with
| Some dst -> dst
| None when marshall -> "index.odoc-index"
| None -> "index.json"
in
let input_files =
Fpath.Set.fold (fun path acc -> Cmd.(acc % p path)) input_files Cmd.empty
in
let marshall = if marshall then Cmd.v "--marshall" else Cmd.empty in
let cmd =
Cmd.(odoc % "compile-index" %% marshall %% v "-o" % p dst %% input_files)
in
let desc = "Generating search index" in
let lines = submit desc cmd (Some dst) in
if not ignore_output then
add_prefixed_output cmd link_output (Fpath.to_string dst) lines

let html_generate ~output_dir ?(ignore_output = false) ?(assets = []) ?source
?(search_uris = []) ~input_file:file () =
let open Cmd in
Expand Down
7 changes: 7 additions & 0 deletions src/driver/odoc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,13 @@ val link :
libs:(string * Fpath.t) list ->
unit ->
unit
val compile_index :
?ignore_output:bool ->
?dst:string ->
marshall:bool ->
input_files:Fpath.set ->
unit ->
unit
val html_generate :
output_dir:string ->
?ignore_output:bool ->
Expand Down
1 change: 1 addition & 0 deletions src/driver/odoc_driver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -514,6 +514,7 @@ let run libs verbose odoc_dir html_dir stats nb_workers =
(fun () ->
let compiled = Compile.compile odoc_dir all in
let linked = Compile.link compiled in
let () = Compile.index linked in
let () = Compile.html_generate html_dir linked in
let _ = Odoc.support_files html_dir in
())
Expand Down

0 comments on commit 205afd9

Please sign in to comment.