Skip to content

Commit a3b7ab0

Browse files
committed
New html-generate-impl command: update driver
1 parent 63894ba commit a3b7ab0

File tree

3 files changed

+34
-7
lines changed

3 files changed

+34
-7
lines changed

src/driver/compile.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -236,7 +236,7 @@ let html_generate output_dir linked =
236236
match l.kind with
237237
| `Intf { hidden = true; _ } -> ()
238238
| `Impl { src_path; _ } ->
239-
Odoc.html_generate ~search_uris:[] ~output_dir ~input_file
239+
Odoc.html_generate_impl ~search_uris:[] ~output_dir ~input_file
240240
~source:src_path ();
241241
Atomic.incr Stats.stats.generated_units
242242
| _ ->

src/driver/odoc.ml

Lines changed: 24 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -130,11 +130,8 @@ let compile_index ?(ignore_output = false) ~output_file ~json ~docs ~libs () =
130130
add_prefixed_output cmd link_output (Fpath.to_string output_file) lines)
131131

132132
let html_generate ~output_dir ?index ?(ignore_output = false) ?(assets = [])
133-
?source ?(search_uris = []) ~input_file:file () =
133+
?(search_uris = []) ~input_file:file () =
134134
let open Cmd in
135-
let source =
136-
match source with None -> empty | Some source -> v "--source" % p source
137-
in
138135
let index =
139136
match index with None -> empty | Some idx -> v "--index" % p idx
140137
in
@@ -147,8 +144,29 @@ let html_generate ~output_dir ?index ?(ignore_output = false) ?(assets = [])
147144
empty search_uris
148145
in
149146
let cmd =
150-
!odoc % "html-generate" %% source % p file %% assets %% index %% search_uris
151-
% "-o" % output_dir
147+
!odoc % "html-generate" % p file %% assets %% index %% search_uris % "-o"
148+
% output_dir
149+
in
150+
let desc = Printf.sprintf "Generating HTML for %s" (Fpath.to_string file) in
151+
let lines = Cmd_outputs.submit desc cmd None in
152+
if not ignore_output then
153+
Cmd_outputs.(
154+
add_prefixed_output cmd generate_output (Fpath.to_string file) lines)
155+
156+
let html_generate_impl ~output_dir ?(ignore_output = false) ?source
157+
?(search_uris = []) ~input_file:file () =
158+
let open Cmd in
159+
let source =
160+
match source with None -> empty | Some source -> v "--source" % p source
161+
in
162+
let search_uris =
163+
List.fold_left
164+
(fun acc filename -> acc % "--search-uri" % p filename)
165+
empty search_uris
166+
in
167+
let cmd =
168+
!odoc % "html-generate-impl" %% source % p file %% search_uris % "-o"
169+
% output_dir
152170
in
153171
let desc = Printf.sprintf "Generating HTML for %s" (Fpath.to_string file) in
154172
let lines = Cmd_outputs.submit desc cmd None in

src/driver/odoc.mli

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,11 +49,20 @@ val html_generate :
4949
?index:Fpath.t ->
5050
?ignore_output:bool ->
5151
?assets:string list ->
52+
?search_uris:Fpath.t list ->
53+
input_file:Fpath.t ->
54+
unit ->
55+
unit
56+
57+
val html_generate_impl :
58+
output_dir:string ->
59+
?ignore_output:bool ->
5260
?source:Fpath.t ->
5361
?search_uris:Fpath.t list ->
5462
input_file:Fpath.t ->
5563
unit ->
5664
unit
65+
5766
val support_files : Fpath.t -> string list
5867

5968
val count_occurrences : Fpath.t -> string list

0 commit comments

Comments
 (0)