@@ -242,7 +242,7 @@ let link : compiled list -> _ =
242242 c
243243 | _ ->
244244 Logs. debug (fun m -> m " linking %a" Fpath. pp c.odoc_file);
245- link c.odoc_file c.odocl_file c.enable_warnings;
245+ if c.to_output then link c.odoc_file c.odocl_file c.enable_warnings;
246246 (match c.kind with
247247 | `Intf _ -> Atomic. incr Stats. stats.linked_units
248248 | `Mld -> Atomic. incr Stats. stats.linked_mlds
@@ -262,7 +262,7 @@ let sherlodoc_index_one ~output_dir (index : Odoc_unit.index) =
262262 Sherlodoc. index ~format: `js ~inputs ~dst () ;
263263 rel_path
264264
265- let html_generate ~occurrence_file output_dir linked =
265+ let html_generate ~occurrence_file ~ remaps output_dir linked =
266266 let tbl = Hashtbl. create 10 in
267267 let _ = OS.Dir. create output_dir |> Result. get_ok in
268268 Sherlodoc. js Fpath. (output_dir // Sherlodoc. js_file);
@@ -289,34 +289,43 @@ let html_generate ~occurrence_file output_dir linked =
289289 rel_path
290290 | Some p -> Promise. await p
291291 in
292- let html_generate : linked -> unit =
293- fun l ->
294- let output_dir = Fpath. to_string output_dir in
295- let input_file = l.odocl_file in
296- match l.kind with
297- | `Intf { hidden = true ; _ } -> ()
298- | `Impl { src_path; _ } ->
299- Odoc. html_generate_source ~search_uris: [] ~output_dir ~input_file
300- ~source: src_path () ;
301- Odoc. html_generate_source ~search_uris: [] ~output_dir ~input_file
302- ~source: src_path ~as_json: true () ;
303- Atomic. incr Stats. stats.generated_units
304- | `Asset ->
305- Odoc. html_generate_asset ~output_dir ~input_file: l.odoc_file
306- ~asset_path: l.input_file ()
307- | _ ->
308- let search_uris, index =
309- match l.index with
310- | None -> (None , None )
311- | Some index ->
312- let db_path = compile_index index in
313- let search_uris = [ db_path; Sherlodoc. js_file ] in
314- let index = index.output_file in
315- (Some search_uris, Some index)
316- in
317- Odoc. html_generate ?search_uris ?index ~output_dir ~input_file () ;
318- Odoc. html_generate ?search_uris ?index ~output_dir ~input_file
319- ~as_json: true () ;
320- Atomic. incr Stats. stats.generated_units
292+ let html_generate : Fpath.t option -> linked -> unit =
293+ fun remap_file l ->
294+ (if l.to_output then
295+ let output_dir = Fpath. to_string output_dir in
296+ let input_file = l.odocl_file in
297+ match l.kind with
298+ | `Intf { hidden = true ; _ } -> ()
299+ | `Impl { src_path; _ } ->
300+ Odoc. html_generate_source ~search_uris: [] ~output_dir ~input_file
301+ ~source: src_path () ;
302+ Odoc. html_generate_source ~search_uris: [] ~output_dir ~input_file
303+ ~source: src_path ~as_json: true () ;
304+ Atomic. incr Stats. stats.generated_units
305+ | `Asset ->
306+ Odoc. html_generate_asset ~output_dir ~input_file: l.odoc_file
307+ ~asset_path: l.input_file ()
308+ | _ ->
309+ let search_uris, index =
310+ match l.index with
311+ | None -> (None , None )
312+ | Some index ->
313+ let db_path = compile_index index in
314+ let search_uris = [ db_path; Sherlodoc. js_file ] in
315+ let index = index.output_file in
316+ (Some search_uris, Some index)
317+ in
318+ Odoc. html_generate ?search_uris ?index ~remap: remap_file ~output_dir
319+ ~input_file () ;
320+ Odoc. html_generate ?search_uris ?index ~output_dir ~input_file
321+ ~as_json: true () );
322+ Atomic. incr Stats. stats.generated_units
321323 in
322- Fiber.List. iter html_generate linked
324+ if List. length remaps = 0 then Fiber.List. iter (html_generate None ) linked
325+ else
326+ Bos.OS.File. with_tmp_oc " remap.%s.txt"
327+ (fun fpath oc () ->
328+ List. iter (fun (a , b ) -> Printf. fprintf oc " %s:%s\n %!" a b) remaps;
329+ Fiber.List. iter (html_generate (Some fpath)) linked)
330+ ()
331+ |> ignore
0 commit comments