Skip to content

Commit 1bdec53

Browse files
committed
Enable remapping of links to ocaml.org
When running in this mode, e.g. `odoc_driver opam -p odoc --remap`, only the documentation for the selected packages -- odoc in this case -- will be generated. Links to other packages will be remapped to point to that package's documentation pages on ocaml.org.
1 parent 78ae7e5 commit 1bdec53

15 files changed

+137
-65
lines changed

src/driver/common_args.ml

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,10 @@ let generate_grep =
5252
let doc = "Show html-generate commands containing the string" in
5353
Arg.(value & opt (some string) None & info [ "html-grep" ] ~doc)
5454

55+
let remap =
56+
let doc = "Remap paths in non-selected packages to ocaml.org" in
57+
Arg.(value & flag & info [ "remap" ] ~doc)
58+
5559
type t = {
5660
verbose : bool;
5761
odoc_dir : Fpath.t;
@@ -65,6 +69,7 @@ type t = {
6569
compile_grep : string option;
6670
link_grep : string option;
6771
generate_grep : string option;
72+
remap : bool;
6873
}
6974

7075
let term =
@@ -82,7 +87,8 @@ let term =
8287
and+ odoc_bin = odoc_bin
8388
and+ compile_grep = compile_grep
8489
and+ link_grep = link_grep
85-
and+ generate_grep = generate_grep in
90+
and+ generate_grep = generate_grep
91+
and+ remap = remap in
8692
{
8793
verbose;
8894
odoc_dir;
@@ -96,4 +102,5 @@ let term =
96102
compile_grep;
97103
link_grep;
98104
generate_grep;
105+
remap;
99106
}

src/driver/compile.ml

Lines changed: 41 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -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

src/driver/compile.mli

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,4 +14,9 @@ type linked
1414

1515
val link : compiled list -> linked list
1616

17-
val html_generate : occurrence_file:Fpath.t -> Fpath.t -> linked list -> unit
17+
val html_generate :
18+
occurrence_file:Fpath.t ->
19+
remaps:(string * string) list ->
20+
Fpath.t ->
21+
linked list ->
22+
unit

src/driver/dune_style.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -122,7 +122,8 @@ let of_dune_build dir =
122122
assets =
123123
[]
124124
(* When dune has a notion of doc assets, do something *);
125-
enable_warnings = false;
125+
selected = false;
126+
remaps = [];
126127
pkg_dir;
127128
other_docs = [];
128129
config = Global_config.empty;

src/driver/landing_pages.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ let make_index ~dirs ~rel_dir ?index ~content () =
1818
odoc_file;
1919
odocl_file;
2020
enable_warnings = false;
21+
to_output = true;
2122
kind = `Mld;
2223
index;
2324
}

src/driver/odoc.ml

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -180,7 +180,7 @@ let compile_index ?(ignore_output = false) ~output_file ?occurrence_file ~json
180180
ignore @@ Cmd_outputs.submit log desc cmd (Some output_file)
181181

182182
let html_generate ~output_dir ?index ?(ignore_output = false)
183-
?(search_uris = []) ?(as_json = false) ~input_file:file () =
183+
?(search_uris = []) ?(remap = None) ?(as_json = false) ~input_file:file () =
184184
let open Cmd in
185185
let index =
186186
match index with None -> empty | Some idx -> v "--index" % p idx
@@ -193,6 +193,9 @@ let html_generate ~output_dir ?index ?(ignore_output = false)
193193
let cmd =
194194
!odoc % "html-generate" % p file %% index %% search_uris % "-o" % output_dir
195195
in
196+
let cmd =
197+
match remap with None -> cmd | Some f -> cmd % "--remap-file" % p f
198+
in
196199
let cmd = if as_json then cmd % "--as-json" else cmd in
197200
let desc = Printf.sprintf "Generating HTML for %s" (Fpath.to_string file) in
198201
let log =

src/driver/odoc.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ val html_generate :
5555
?index:Fpath.t ->
5656
?ignore_output:bool ->
5757
?search_uris:Fpath.t list ->
58+
?remap:Fpath.t option ->
5859
?as_json:bool ->
5960
input_file:Fpath.t ->
6061
unit ->

src/driver/odoc_driver.ml

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -133,6 +133,7 @@ let run mode
133133
compile_grep;
134134
link_grep;
135135
generate_grep;
136+
remap;
136137
} =
137138
Option.iter (fun odoc_bin -> Odoc.odoc := Bos.Cmd.v odoc_bin) odoc_bin;
138139
let _ = Voodoo.find_universe_and_version "foo" in
@@ -195,6 +196,14 @@ let run mode
195196
| _ -> failwith "Error, expecting singleton library in voodoo mode")
196197
| _ -> None
197198
in
199+
let remaps =
200+
if remap then
201+
List.concat_map
202+
(fun (_, pkg) -> pkg.Packages.remaps)
203+
(Util.StringMap.bindings all)
204+
else []
205+
in
206+
Logs.debug (fun m -> m "XXXX Remaps length: %d" (List.length remaps));
198207
let () =
199208
Eio.Fiber.both
200209
(fun () ->
@@ -204,7 +213,7 @@ let run mode
204213
let odocl_dir = Option.value odocl_dir ~default:odoc_dir in
205214
{ Odoc_unit.odoc_dir; odocl_dir; index_dir; mld_dir }
206215
in
207-
Odoc_units_of.packages ~dirs ~extra_paths all
216+
Odoc_units_of.packages ~dirs ~extra_paths ~remap all
208217
in
209218
Compile.init_stats units;
210219
let compiled =
@@ -229,7 +238,9 @@ let run mode
229238
let () = Odoc.count_occurrences ~input:[ odoc_dir ] ~output in
230239
output
231240
in
232-
let () = Compile.html_generate ~occurrence_file html_dir linked in
241+
let () =
242+
Compile.html_generate ~occurrence_file ~remaps html_dir linked
243+
in
233244
let _ = Odoc.support_files html_dir in
234245
())
235246
(fun () -> render_stats env nb_workers)

src/driver/odoc_unit.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ type 'a unit = {
5858
pkgname : string option;
5959
index : index option;
6060
enable_warnings : bool;
61+
to_output : bool;
6162
kind : 'a;
6263
}
6364

src/driver/odoc_unit.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ type 'a unit = {
3333
pkgname : string option;
3434
index : index option;
3535
enable_warnings : bool;
36+
to_output : bool;
3637
kind : 'a;
3738
}
3839

0 commit comments

Comments
 (0)