Skip to content

Commit b09cf3b

Browse files
authored
Merge pull request #1250 from panglesd/root-in-sidebar
Dedicated sidebar file
2 parents 8f6beac + af779c3 commit b09cf3b

File tree

32 files changed

+450
-148
lines changed

32 files changed

+450
-148
lines changed

CHANGES.md

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,10 @@
1616
Absolute (`{!/foo}`), relative (`{!./foo}`) and package-local (`{!//foo}`)
1717
are added.
1818
- Add a marshalled search index consumable by sherlodoc (@EmileTrotignon, @panglesd, #1084)
19-
- Add a `--index` argument to pass indexes to the document generation, currently
20-
used for sidebar (@panglesd, #1145)
19+
- Add a `odoc sidebar-generate` command to generate a sidebar file (@panglesd,
20+
#1250)
21+
- Add a `--sidebar` argument to pass sidebars to the document generation
22+
(@panglesd, #1145, #1250)
2123
- Allow referencing of polymorphic constructors in polymorphic variant type
2224
aliases (@panglesd, #1115)
2325
- Added a `--occurrences` argument to the `compile-index` command to output the

src/document/sidebar.ml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,16 +2,18 @@ open Odoc_utils
22
open Types
33
module Id = Odoc_model.Paths.Identifier
44

5+
type entry = Url.t option * Inline.one
6+
57
module Toc : sig
6-
type t
8+
type t = entry Tree.t
79

810
val of_page_hierarchy : Odoc_index.Page_hierarchy.t -> t
911

1012
val of_skeleton : Odoc_index.Skeleton.t -> t
1113

1214
val to_block : prune:bool -> Url.Path.t -> t -> Block.t
1315
end = struct
14-
type t = (Url.t option * Inline.one) Tree.t
16+
type t = entry Tree.t
1517

1618
let of_page_hierarchy (dir : Odoc_index.Page_hierarchy.t) : t =
1719
let f index =

src/document/sidebar.mli

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,12 @@
1-
type t
1+
open Odoc_utils
2+
open Types
3+
4+
type entry = Url.t option * Inline.one
5+
6+
type pages = { name : string; pages : entry Tree.t }
7+
type library = { name : string; units : entry Tree.t list }
8+
9+
type t = { pages : pages list; libraries : library list }
210

311
val of_lang : Odoc_index.t -> t
412

src/driver/compile.ml

Lines changed: 15 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -269,15 +269,22 @@ let html_generate ~occurrence_file ~remaps output_dir linked =
269269
let compile_index : Odoc_unit.index -> _ =
270270
fun index ->
271271
let compile_index_one
272-
({ pkg_args; output_file; json; search_dir = _ } as index :
272+
({ pkg_args; output_file; json; search_dir = _; sidebar } as index :
273273
Odoc_unit.index) =
274274
let libs_linked = Odoc_unit.Pkg_args.linked_libs pkg_args in
275275
let pages_linked = Odoc_unit.Pkg_args.linked_pages pkg_args in
276276
let () =
277277
Odoc.compile_index ~json ~occurrence_file ~output_file ~libs:libs_linked
278278
~docs:pages_linked ()
279279
in
280-
sherlodoc_index_one ~output_dir index
280+
let sidebar =
281+
match sidebar with
282+
| None -> None
283+
| Some { output_file; json } ->
284+
Odoc.sidebar_generate ~output_file ~json index.output_file ();
285+
Some output_file
286+
in
287+
(sherlodoc_index_one ~output_dir index, sidebar)
281288
in
282289
match Hashtbl.find_opt tbl index.output_file with
283290
| None ->
@@ -306,18 +313,17 @@ let html_generate ~occurrence_file ~remaps output_dir linked =
306313
Odoc.html_generate_asset ~output_dir ~input_file:l.odoc_file
307314
~asset_path:l.input_file ()
308315
| _ ->
309-
let search_uris, index =
316+
let search_uris, sidebar =
310317
match l.index with
311318
| None -> (None, None)
312319
| Some index ->
313-
let db_path = compile_index index in
320+
let db_path, sidebar = compile_index index in
314321
let search_uris = [ db_path; Sherlodoc.js_file ] in
315-
let index = index.output_file in
316-
(Some search_uris, Some index)
322+
(Some search_uris, sidebar)
317323
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
324+
Odoc.html_generate ?search_uris ?sidebar ?remap:remap_file
325+
~output_dir ~input_file ();
326+
Odoc.html_generate ?search_uris ?sidebar ~output_dir ~input_file
321327
~as_json:true ());
322328
Atomic.incr Stats.stats.generated_units
323329
in

src/driver/odoc.ml

Lines changed: 19 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,8 @@ end
1818

1919
let index_filename = "index.odoc-index"
2020

21+
let sidebar_filename = "sidebar.odoc-sidebar"
22+
2123
type compile_deps = { digest : Digest.t; deps : (string * Digest.t) list }
2224

2325
let odoc = ref (Cmd.v "odoc")
@@ -179,11 +181,26 @@ let compile_index ?(ignore_output = false) ~output_file ?occurrence_file ~json
179181
in
180182
ignore @@ Cmd_outputs.submit log desc cmd (Some output_file)
181183

182-
let html_generate ~output_dir ?index ?(ignore_output = false)
184+
let sidebar_generate ?(ignore_output = false) ~output_file ~json input_file () =
185+
let json = if json then Cmd.v "--json" else Cmd.empty in
186+
let cmd =
187+
Cmd.(
188+
!odoc % "sidebar-generate" %% json %% v "-o" % p output_file
189+
% p input_file)
190+
in
191+
let desc =
192+
Printf.sprintf "Generating sidebar for %s" (Fpath.to_string output_file)
193+
in
194+
let log =
195+
if ignore_output then None else Some (`Generate, Fpath.to_string output_file)
196+
in
197+
ignore @@ Cmd_outputs.submit log desc cmd (Some output_file)
198+
199+
let html_generate ~output_dir ?sidebar ?(ignore_output = false)
183200
?(search_uris = []) ?remap ?(as_json = false) ~input_file:file () =
184201
let open Cmd in
185202
let index =
186-
match index with None -> empty | Some idx -> v "--index" % p idx
203+
match sidebar with None -> empty | Some idx -> v "--sidebar" % p idx
187204
in
188205
let search_uris =
189206
List.fold_left

src/driver/odoc.mli

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ module Id : sig
66
end
77

88
val index_filename : string
9+
val sidebar_filename : string
910

1011
val odoc : Bos.Cmd.t ref
1112

@@ -50,9 +51,17 @@ val compile_index :
5051
unit ->
5152
unit
5253

54+
val sidebar_generate :
55+
?ignore_output:bool ->
56+
output_file:Fpath.t ->
57+
json:bool ->
58+
Fpath.t ->
59+
unit ->
60+
unit
61+
5362
val html_generate :
5463
output_dir:string ->
55-
?index:Fpath.t ->
64+
?sidebar:Fpath.t ->
5665
?ignore_output:bool ->
5766
?search_uris:Fpath.t list ->
5867
?remap:Fpath.t ->

src/driver/odoc_unit.ml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -36,11 +36,14 @@ module Pkg_args = struct
3636
x.odoc_dir Fpath.pp x.odocl_dir sfp_pp x.pages sfp_pp x.libs
3737
end
3838

39+
type sidebar = { output_file : Fpath.t; json : bool }
40+
3941
type index = {
4042
pkg_args : Pkg_args.t;
4143
output_file : Fpath.t;
4244
json : bool;
4345
search_dir : Fpath.t;
46+
sidebar : sidebar option;
4447
}
4548

4649
let pp_index fmt x =

src/driver/odoc_unit.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,11 +16,13 @@ module Pkg_args : sig
1616
val pp : t Fmt.t
1717
end
1818

19+
type sidebar = { output_file : Fpath.t; json : bool }
1920
type index = {
2021
pkg_args : Pkg_args.t;
2122
output_file : Fpath.t;
2223
json : bool;
2324
search_dir : Fpath.t;
25+
sidebar : sidebar option;
2426
}
2527

2628
type 'a unit = {

src/driver/odoc_units_of.ml

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,17 @@ let packages ~dirs ~extra_paths ~remap (pkgs : Packages.t list) : t list =
8484
in
8585
let pkg_args = base_args pkg pkg_libs in
8686
let output_file = Fpath.(index_dir / pkg.name / Odoc.index_filename) in
87-
{ pkg_args; output_file; json = false; search_dir = pkg.pkg_dir }
87+
let sidebar =
88+
let output_file = Fpath.(index_dir / pkg.name / Odoc.sidebar_filename) in
89+
{ output_file; json = false }
90+
in
91+
{
92+
pkg_args;
93+
output_file;
94+
json = false;
95+
search_dir = pkg.pkg_dir;
96+
sidebar = Some sidebar;
97+
}
8898
in
8999

90100
let make_unit ~name ~kind ~rel_dir ~input_file ~pkg ~lib_deps ~enable_warnings

src/html/generator.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -590,3 +590,7 @@ let filepath ~config url = Link.Path.as_filename ~config url
590590
let doc ~config ~xref_base_uri b =
591591
let resolve = Link.Base xref_base_uri in
592592
block ~config ~resolve b
593+
594+
let inline ~config ~xref_base_uri b =
595+
let resolve = Link.Base xref_base_uri in
596+
inline ~config ~resolve b

0 commit comments

Comments
 (0)