Skip to content

Commit d6fea07

Browse files
authored
Merge pull request #1185 from panglesd/generate-assets
Add ability to call generate commands on asset units
2 parents 3e332c9 + 2444176 commit d6fea07

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

41 files changed

+492
-438
lines changed

CHANGES.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@
2626
(@panglesd, #1076).
2727
- Added a `compile-asset` command (@EmileTrotignon, @panglesd, #1170)
2828
- Allow referencing assets (@panglesd, #1171)
29+
- Added a `--asset-path` arg to `html-generate` (@panglesd, #1185)
2930

3031
### Changed
3132

src/document/renderer.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ type input =
2424
type 'a t = {
2525
name : string;
2626
render : 'a -> Types.Block.t option -> Types.Document.t -> page list;
27-
extra_documents : 'a -> input -> Types.Document.t list;
27+
filepath : 'a -> Url.Path.t -> Fpath.t;
2828
}
2929

3030
let document_of_page ~syntax v =

src/document/types.ml

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -196,13 +196,8 @@ and Source_page : sig
196196
end =
197197
Source_page
198198

199-
and Asset : sig
200-
type t = { url : Url.Path.t; src : Fpath.t }
201-
end =
202-
Asset
203-
204199
module Document = struct
205-
type t = Page of Page.t | Source_page of Source_page.t | Asset of Asset.t
200+
type t = Page of Page.t | Source_page of Source_page.t
206201
end
207202

208203
let inline ?(attr = []) desc = Inline.{ attr; desc }

src/driver/compile.ml

Lines changed: 103 additions & 87 deletions
Original file line numberDiff line numberDiff line change
@@ -2,37 +2,43 @@
22

33
type compiled = Odoc_unit.t
44

5-
let mk_byhash (pkgs : Odoc_unit.intf Odoc_unit.unit list) =
5+
let mk_byhash (pkgs : Odoc_unit.t list) =
66
List.fold_left
7-
(fun acc (u : Odoc_unit.intf Odoc_unit.unit) ->
7+
(fun acc (u : Odoc_unit.t) ->
88
match u.Odoc_unit.kind with
9-
| `Intf { hash; _ } -> Util.StringMap.add hash u acc)
9+
| `Intf { hash; _ } as kind -> Util.StringMap.add hash { u with kind } acc
10+
| _ -> acc)
1011
Util.StringMap.empty pkgs
1112

1213
let init_stats (units : Odoc_unit.t list) =
13-
let total, total_impl, non_hidden, mlds, indexes =
14+
let total, total_impl, non_hidden, mlds, assets, indexes =
1415
List.fold_left
15-
(fun (total, total_impl, non_hidden, mlds, indexes) (unit : Odoc_unit.t) ->
16+
(fun (total, total_impl, non_hidden, mlds, assets, indexes)
17+
(unit : Odoc_unit.t) ->
1618
let total = match unit.kind with `Intf _ -> total + 1 | _ -> total in
1719
let total_impl =
1820
match unit.kind with `Impl _ -> total_impl + 1 | _ -> total_impl
1921
in
22+
let assets =
23+
match unit.kind with `Asset -> assets + 1 | _ -> assets
24+
in
2025
let indexes = Fpath.Set.add unit.index.output_file indexes in
2126
let non_hidden =
2227
match unit.kind with
2328
| `Intf { hidden = false; _ } -> non_hidden + 1
2429
| _ -> non_hidden
2530
in
2631
let mlds = match unit.kind with `Mld -> mlds + 1 | _ -> mlds in
27-
(total, total_impl, non_hidden, mlds, indexes))
28-
(0, 0, 0, 0, Fpath.Set.empty)
32+
(total, total_impl, non_hidden, mlds, assets, indexes))
33+
(0, 0, 0, 0, 0, Fpath.Set.empty)
2934
units
3035
in
3136

3237
Atomic.set Stats.stats.total_units total;
3338
Atomic.set Stats.stats.total_impls total_impl;
3439
Atomic.set Stats.stats.non_hidden_units non_hidden;
3540
Atomic.set Stats.stats.total_mlds mlds;
41+
Atomic.set Stats.stats.total_assets assets;
3642
Atomic.set Stats.stats.total_indexes (Fpath.Set.cardinal indexes)
3743

3844
open Eio.Std
@@ -78,93 +84,99 @@ let find_partials odoc_dir : Odoc_unit.intf Odoc_unit.unit Util.StringMap.t * _
7884
| Error _ -> (* odoc_dir doesn't exist...? *) (Util.StringMap.empty, tbl)
7985

8086
let compile ?partial ~partial_dir ?linked_dir:_ (all : Odoc_unit.t list) =
81-
(* let linked_dir = Option.value linked_dir ~default:output_dir in *)
82-
let intf_units, impl_units, mld_units =
83-
List.fold_left
84-
(fun (intf_units, impl_units, page_units) (unit : Odoc_unit.t) ->
85-
match unit with
86-
| { kind = `Intf _; _ } as intf ->
87-
(intf :: intf_units, impl_units, page_units)
88-
| { kind = `Impl _; _ } as impl ->
89-
(intf_units, impl :: impl_units, page_units)
90-
| { kind = `Mld; _ } as mld ->
91-
(intf_units, impl_units, mld :: page_units))
92-
([], [], []) all
93-
in
94-
let hashes = mk_byhash intf_units in
95-
let other_hashes, tbl =
96-
match partial with
97-
| Some _ -> find_partials partial_dir
98-
| None -> (Util.StringMap.empty, Hashtbl.create 10)
99-
in
100-
let all_hashes =
101-
Util.StringMap.union (fun _x o1 _o2 -> Some o1) hashes other_hashes
87+
let hashes = mk_byhash all in
88+
let compile_mod =
89+
(* Modules have a more complicated compilation because:
90+
- They have dependencies and must be compiled in the right order
91+
- In Voodoo mode, there might exists already compiled parts *)
92+
let other_hashes, tbl =
93+
match partial with
94+
| Some _ -> find_partials partial_dir
95+
| None -> (Util.StringMap.empty, Hashtbl.create 10)
96+
in
97+
let all_hashes =
98+
Util.StringMap.union (fun _x o1 _o2 -> Some o1) hashes other_hashes
99+
in
100+
let compile_one compile_other hash =
101+
match Util.StringMap.find_opt hash all_hashes with
102+
| None ->
103+
Logs.debug (fun m -> m "Error locating hash: %s" hash);
104+
Error Not_found
105+
| Some unit ->
106+
let deps = match unit.kind with `Intf { deps; _ } -> deps in
107+
let _fibers =
108+
Fiber.List.map
109+
(fun (other_unit : Odoc_unit.intf Odoc_unit.unit) ->
110+
match compile_other other_unit with
111+
| Ok r -> Some r
112+
| Error _exn ->
113+
Logs.debug (fun m ->
114+
m
115+
"Error during compilation of module %s (hash %s, \
116+
required by %s)"
117+
(Fpath.filename other_unit.input_file)
118+
(match other_unit.kind with
119+
| `Intf { hash; _ } -> hash)
120+
(Fpath.filename unit.input_file));
121+
None)
122+
deps
123+
in
124+
let includes = Fpath.Set.of_list unit.include_dirs in
125+
Odoc.compile ~output_dir:unit.output_dir ~input_file:unit.input_file
126+
~includes ~parent_id:unit.parent_id;
127+
Atomic.incr Stats.stats.compiled_units;
128+
129+
Ok unit
130+
in
131+
let rec compile_mod :
132+
Odoc_unit.intf Odoc_unit.unit ->
133+
(Odoc_unit.intf Odoc_unit.unit, exn) Result.t =
134+
fun unit ->
135+
let hash = match unit.kind with `Intf { hash; _ } -> hash in
136+
match Hashtbl.find_opt tbl hash with
137+
| Some p -> Promise.await p
138+
| None ->
139+
let p, r = Promise.create () in
140+
Hashtbl.add tbl hash p;
141+
let result = compile_one compile_mod hash in
142+
Promise.resolve r result;
143+
result
144+
in
145+
compile_mod
102146
in
103-
let compile_one compile_other hash =
104-
match Util.StringMap.find_opt hash all_hashes with
105-
| None ->
106-
Logs.debug (fun m -> m "Error locating hash: %s" hash);
107-
Error Not_found
108-
| Some unit ->
109-
let deps = match unit.kind with `Intf { deps; _ } -> deps in
110-
let _fibers =
111-
Fiber.List.map
112-
(fun other_unit ->
113-
match compile_other other_unit with
114-
| Ok r -> Some r
115-
| Error _exn ->
116-
Logs.debug (fun m ->
117-
m "Missing module %s (hash %s, required by %s)" "TODO"
118-
(* n h *) "TODO" "TODO" (* unit.m_name *));
119-
None)
120-
deps
121-
in
147+
148+
let compile (unit : Odoc_unit.t) =
149+
match unit.kind with
150+
| `Intf _ as kind ->
151+
(compile_mod { unit with kind } :> (Odoc_unit.t, _) Result.t)
152+
| `Impl src ->
153+
let includes = Fpath.Set.of_list unit.include_dirs in
154+
let source_id = src.src_id in
155+
Odoc.compile_impl ~output_dir:unit.output_dir
156+
~input_file:unit.input_file ~includes ~parent_id:unit.parent_id
157+
~source_id;
158+
Atomic.incr Stats.stats.compiled_impls;
159+
Ok unit
160+
| `Asset ->
161+
Odoc.compile_asset ~output_dir:unit.output_dir ~parent_id:unit.parent_id
162+
~name:(Fpath.filename unit.input_file);
163+
Atomic.incr Stats.stats.compiled_assets;
164+
Ok unit
165+
| `Mld ->
122166
let includes = Fpath.Set.of_list unit.include_dirs in
123167
Odoc.compile ~output_dir:unit.output_dir ~input_file:unit.input_file
124168
~includes ~parent_id:unit.parent_id;
125-
Atomic.incr Stats.stats.compiled_units;
126-
169+
Atomic.incr Stats.stats.compiled_mlds;
127170
Ok unit
128171
in
129-
130-
let rec compile_mod :
131-
Odoc_unit.intf Odoc_unit.unit ->
132-
(Odoc_unit.intf Odoc_unit.unit, exn) Result.t =
133-
fun unit ->
134-
let hash = match unit.kind with `Intf { hash; _ } -> hash in
135-
match Hashtbl.find_opt tbl hash with
136-
| Some p -> Promise.await p
137-
| None ->
138-
let p, r = Promise.create () in
139-
Hashtbl.add tbl hash p;
140-
let result = compile_one compile_mod hash in
141-
Promise.resolve r result;
142-
result
143-
in
144-
let to_build = Util.StringMap.bindings hashes |> List.map snd in
145-
let mod_results = Fiber.List.map compile_mod to_build in
146-
let compile_mld (unit : Odoc_unit.mld Odoc_unit.unit) =
147-
let includes = Fpath.Set.of_list unit.include_dirs in
148-
Odoc.compile ~output_dir:unit.output_dir ~input_file:unit.input_file
149-
~includes ~parent_id:unit.parent_id;
150-
Atomic.incr Stats.stats.compiled_mlds
151-
in
152-
let () = Fiber.List.iter compile_mld mld_units in
153-
let compile_impl (unit : Odoc_unit.impl Odoc_unit.unit) =
154-
let includes = Fpath.Set.of_list unit.include_dirs in
155-
let source_id = match unit.kind with `Impl src -> src.src_id in
156-
Odoc.compile_impl ~output_dir:unit.output_dir ~input_file:unit.input_file
157-
~includes ~parent_id:unit.parent_id ~source_id;
158-
Atomic.incr Stats.stats.compiled_impls
159-
in
160-
let () = Fiber.List.iter compile_impl impl_units in
161-
let zipped_res =
162-
List.map2
163-
(fun Odoc_unit.{ kind = `Intf { hash; _ }; _ } b -> (hash, b))
164-
to_build mod_results
165-
in
172+
let res = Fiber.List.map compile all in
173+
(* For voodoo mode, we need to keep which modules successfully compiled *)
166174
let zipped =
167-
List.filter_map (function a, Ok b -> Some (a, b) | _ -> None) zipped_res
175+
List.filter_map
176+
(function
177+
| Ok (Odoc_unit.{ kind = `Intf { hash; _ }; _ } as b) -> Some (hash, b)
178+
| _ -> None)
179+
res
168180
in
169181
(match partial with
170182
| Some l -> marshal (zipped, hashes) Fpath.(l / "index.m")
@@ -193,6 +205,7 @@ let link : compiled list -> _ =
193205
(match c.kind with
194206
| `Intf _ -> Atomic.incr Stats.stats.linked_units
195207
| `Mld -> Atomic.incr Stats.stats.linked_mlds
208+
| `Asset -> ()
196209
| `Impl _ -> Atomic.incr Stats.stats.linked_impls);
197210
c
198211
in
@@ -239,6 +252,9 @@ let html_generate output_dir linked =
239252
Odoc.html_generate_source ~search_uris:[] ~output_dir ~input_file
240253
~source:src_path ();
241254
Atomic.incr Stats.stats.generated_units
255+
| `Asset ->
256+
Odoc.html_generate_asset ~output_dir ~input_file:l.odoc_file
257+
~asset_path:l.input_file ()
242258
| _ ->
243259
let db_path = compile_index l.index in
244260
let search_uris = [ db_path; Sherlodoc.js_file ] in

src/driver/dune_style.ml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,9 @@ let of_dune_build dir =
5353
version = "1.0";
5454
libraries = [ lib ];
5555
mlds = [];
56+
assets =
57+
[]
58+
(* When dune has a notion of doc assets, do something *);
5659
pkg_dir;
5760
other_docs = Fpath.Set.empty;
5861
} )

src/driver/odoc.ml

Lines changed: 30 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,20 @@ let compile ~output_dir ~input_file:file ~includes ~parent_id =
4545
Cmd_outputs.(
4646
add_prefixed_output cmd compile_output (Fpath.to_string file) lines)
4747

48+
let compile_asset ~output_dir ~name ~parent_id =
49+
let open Cmd in
50+
let output_file =
51+
Some Fpath.(output_dir // parent_id / ("asset-" ^ name ^ ".odoc"))
52+
in
53+
let cmd =
54+
!odoc % "compile-asset" % "--name" % name % "--output-dir" % p output_dir
55+
in
56+
57+
let cmd = cmd % "--parent-id" % Fpath.to_string parent_id in
58+
let desc = Printf.sprintf "Compiling %s" name in
59+
let lines = Cmd_outputs.submit desc cmd output_file in
60+
Cmd_outputs.(add_prefixed_output cmd compile_output name lines)
61+
4862
let compile_impl ~output_dir ~input_file:file ~includes ~parent_id ~source_id =
4963
let open Cmd in
5064
let includes =
@@ -129,30 +143,39 @@ let compile_index ?(ignore_output = false) ~output_file ~json ~docs ~libs () =
129143
Cmd_outputs.(
130144
add_prefixed_output cmd link_output (Fpath.to_string output_file) lines)
131145

132-
let html_generate ~output_dir ?index ?(ignore_output = false) ?(assets = [])
146+
let html_generate ~output_dir ?index ?(ignore_output = false)
133147
?(search_uris = []) ~input_file:file () =
134148
let open Cmd in
135149
let index =
136150
match index with None -> empty | Some idx -> v "--index" % p idx
137151
in
138-
let assets =
139-
List.fold_left (fun acc filename -> acc % "--asset" % filename) empty assets
140-
in
141152
let search_uris =
142153
List.fold_left
143154
(fun acc filename -> acc % "--search-uri" % p filename)
144155
empty search_uris
145156
in
146157
let cmd =
147-
!odoc % "html-generate" % p file %% assets %% index %% search_uris % "-o"
148-
% output_dir
158+
!odoc % "html-generate" % p file %% index %% search_uris % "-o" % output_dir
149159
in
150160
let desc = Printf.sprintf "Generating HTML for %s" (Fpath.to_string file) in
151161
let lines = Cmd_outputs.submit desc cmd None in
152162
if not ignore_output then
153163
Cmd_outputs.(
154164
add_prefixed_output cmd generate_output (Fpath.to_string file) lines)
155165

166+
let html_generate_asset ~output_dir ?(ignore_output = false) ~input_file:file
167+
~asset_path () =
168+
let open Cmd in
169+
let cmd =
170+
!odoc % "html-generate-asset" % "-o" % output_dir % "--asset-unit" % p file
171+
% p asset_path
172+
in
173+
let desc = Printf.sprintf "Copying asset %s" (Fpath.to_string file) in
174+
let lines = Cmd_outputs.submit desc cmd None in
175+
if not ignore_output then
176+
Cmd_outputs.(
177+
add_prefixed_output cmd generate_output (Fpath.to_string file) lines)
178+
156179
let html_generate_source ~output_dir ?(ignore_output = false) ~source
157180
?(search_uris = []) ~input_file:file () =
158181
let open Cmd in
@@ -163,7 +186,7 @@ let html_generate_source ~output_dir ?(ignore_output = false) ~source
163186
empty search_uris
164187
in
165188
let cmd =
166-
!odoc % "html-generate-impl" %% file % p source %% search_uris % "-o"
189+
!odoc % "html-generate-source" %% file % p source %% search_uris % "-o"
167190
% output_dir
168191
in
169192
let desc = Printf.sprintf "Generating HTML for %s" (Fpath.to_string source) in

src/driver/odoc.mli

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,8 @@ val compile :
2424
parent_id:id ->
2525
unit
2626

27+
val compile_asset : output_dir:Fpath.t -> name:string -> parent_id:id -> unit
28+
2729
val link :
2830
?ignore_output:bool ->
2931
input_file:Fpath.t ->
@@ -48,12 +50,19 @@ val html_generate :
4850
output_dir:string ->
4951
?index:Fpath.t ->
5052
?ignore_output:bool ->
51-
?assets:string list ->
5253
?search_uris:Fpath.t list ->
5354
input_file:Fpath.t ->
5455
unit ->
5556
unit
5657

58+
val html_generate_asset :
59+
output_dir:string ->
60+
?ignore_output:bool ->
61+
input_file:Fpath.t ->
62+
asset_path:Fpath.t ->
63+
unit ->
64+
unit
65+
5766
val html_generate_source :
5867
output_dir:string ->
5968
?ignore_output:bool ->

0 commit comments

Comments
 (0)