|
2 | 2 |
|
3 | 3 | type compiled = Odoc_unit.t
|
4 | 4 |
|
5 |
| -let mk_byhash (pkgs : Odoc_unit.intf Odoc_unit.unit list) = |
| 5 | +let mk_byhash (pkgs : Odoc_unit.t list) = |
6 | 6 | List.fold_left
|
7 |
| - (fun acc (u : Odoc_unit.intf Odoc_unit.unit) -> |
| 7 | + (fun acc (u : Odoc_unit.t) -> |
8 | 8 | 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) |
10 | 11 | Util.StringMap.empty pkgs
|
11 | 12 |
|
12 | 13 | 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 = |
14 | 15 | 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) -> |
16 | 18 | let total = match unit.kind with `Intf _ -> total + 1 | _ -> total in
|
17 | 19 | let total_impl =
|
18 | 20 | match unit.kind with `Impl _ -> total_impl + 1 | _ -> total_impl
|
19 | 21 | in
|
| 22 | + let assets = |
| 23 | + match unit.kind with `Asset -> assets + 1 | _ -> assets |
| 24 | + in |
20 | 25 | let indexes = Fpath.Set.add unit.index.output_file indexes in
|
21 | 26 | let non_hidden =
|
22 | 27 | match unit.kind with
|
23 | 28 | | `Intf { hidden = false; _ } -> non_hidden + 1
|
24 | 29 | | _ -> non_hidden
|
25 | 30 | in
|
26 | 31 | 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) |
29 | 34 | units
|
30 | 35 | in
|
31 | 36 |
|
32 | 37 | Atomic.set Stats.stats.total_units total;
|
33 | 38 | Atomic.set Stats.stats.total_impls total_impl;
|
34 | 39 | Atomic.set Stats.stats.non_hidden_units non_hidden;
|
35 | 40 | Atomic.set Stats.stats.total_mlds mlds;
|
| 41 | + Atomic.set Stats.stats.total_assets assets; |
36 | 42 | Atomic.set Stats.stats.total_indexes (Fpath.Set.cardinal indexes)
|
37 | 43 |
|
38 | 44 | open Eio.Std
|
@@ -78,93 +84,99 @@ let find_partials odoc_dir : Odoc_unit.intf Odoc_unit.unit Util.StringMap.t * _
|
78 | 84 | | Error _ -> (* odoc_dir doesn't exist...? *) (Util.StringMap.empty, tbl)
|
79 | 85 |
|
80 | 86 | 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 |
102 | 146 | 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 -> |
122 | 166 | let includes = Fpath.Set.of_list unit.include_dirs in
|
123 | 167 | Odoc.compile ~output_dir:unit.output_dir ~input_file:unit.input_file
|
124 | 168 | ~includes ~parent_id:unit.parent_id;
|
125 |
| - Atomic.incr Stats.stats.compiled_units; |
126 |
| - |
| 169 | + Atomic.incr Stats.stats.compiled_mlds; |
127 | 170 | Ok unit
|
128 | 171 | 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 *) |
166 | 174 | 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 |
168 | 180 | in
|
169 | 181 | (match partial with
|
170 | 182 | | Some l -> marshal (zipped, hashes) Fpath.(l / "index.m")
|
@@ -193,6 +205,7 @@ let link : compiled list -> _ =
|
193 | 205 | (match c.kind with
|
194 | 206 | | `Intf _ -> Atomic.incr Stats.stats.linked_units
|
195 | 207 | | `Mld -> Atomic.incr Stats.stats.linked_mlds
|
| 208 | + | `Asset -> () |
196 | 209 | | `Impl _ -> Atomic.incr Stats.stats.linked_impls);
|
197 | 210 | c
|
198 | 211 | in
|
@@ -239,6 +252,9 @@ let html_generate output_dir linked =
|
239 | 252 | Odoc.html_generate_source ~search_uris:[] ~output_dir ~input_file
|
240 | 253 | ~source:src_path ();
|
241 | 254 | 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 () |
242 | 258 | | _ ->
|
243 | 259 | let db_path = compile_index l.index in
|
244 | 260 | let search_uris = [ db_path; Sherlodoc.js_file ] in
|
|
0 commit comments