Skip to content

Commit a00a1ab

Browse files
committed
Sidebar: Add the global sidebar to implementation pages
1 parent aabd040 commit a00a1ab

File tree

12 files changed

+74
-31
lines changed

12 files changed

+74
-31
lines changed

src/driver/compile.ml

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -300,9 +300,17 @@ let html_generate ~occurrence_file output_dir linked =
300300
match l.kind with
301301
| `Intf { hidden = true; _ } -> ()
302302
| `Impl { src_path; _ } ->
303-
Odoc.html_generate_source ~search_uris:[] ~output_dir ~input_file
303+
let search_uris, sidebar =
304+
match l.index with
305+
| None -> (None, None)
306+
| Some index ->
307+
let db_path, sidebar = compile_index index in
308+
let search_uris = [ db_path; Sherlodoc.js_file ] in
309+
(Some search_uris, sidebar)
310+
in
311+
Odoc.html_generate_source ?search_uris ?sidebar ~output_dir ~input_file
304312
~source:src_path ();
305-
Odoc.html_generate_source ~search_uris:[] ~output_dir ~input_file
313+
Odoc.html_generate_source ?search_uris ?sidebar ~output_dir ~input_file
306314
~source:src_path ~as_json:true ();
307315
Atomic.incr Stats.stats.generated_units
308316
| `Asset ->

src/driver/odoc.ml

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -230,18 +230,21 @@ let html_generate_asset ~output_dir ?(ignore_output = false) ~input_file:file
230230
in
231231
ignore @@ Cmd_outputs.submit log desc cmd None
232232

233-
let html_generate_source ~output_dir ?(ignore_output = false) ~source
233+
let html_generate_source ~output_dir ?(ignore_output = false) ~source ?sidebar
234234
?(search_uris = []) ?(as_json = false) ~input_file:file () =
235235
let open Cmd in
236236
let file = v "--impl" % p file in
237+
let sidebar =
238+
match sidebar with None -> empty | Some idx -> v "--sidebar" % p idx
239+
in
237240
let search_uris =
238241
List.fold_left
239242
(fun acc filename -> acc % "--search-uri" % p filename)
240243
empty search_uris
241244
in
242245
let cmd =
243-
!odoc % "html-generate-source" %% file % p source %% search_uris % "-o"
244-
% output_dir
246+
!odoc % "html-generate-source" %% file %% sidebar % p source %% search_uris
247+
% "-o" % output_dir
245248
in
246249
let cmd = if as_json then cmd % "--as-json" else cmd in
247250

src/driver/odoc.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -80,6 +80,7 @@ val html_generate_source :
8080
output_dir:string ->
8181
?ignore_output:bool ->
8282
source:Fpath.t ->
83+
?sidebar:Fpath.t ->
8384
?search_uris:Fpath.t list ->
8485
?as_json:bool ->
8586
input_file:Fpath.t ->

src/html/generator.ml

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -567,23 +567,32 @@ module Page = struct
567567
Html_page.make ~sidebar ~config ~header ~toc ~breadcrumbs ~url ~uses_katex
568568
content subpages
569569

570-
and source_page ~config sp =
570+
and source_page ~config ~sidebar sp =
571571
let { Source_page.url; contents } = sp in
572572
let resolve = Link.Current sp.url in
573+
let sidebar =
574+
match sidebar with
575+
| None -> None
576+
| Some sidebar ->
577+
let sidebar = Odoc_document.Sidebar.to_block sidebar url in
578+
(Some (block ~config ~resolve sidebar) :> any Html.elt list option)
579+
in
573580
let title = url.Url.Path.name
574581
and doc = Html_source.html_of_doc ~config ~resolve contents in
575582
let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~url in
576583
let header =
577584
items ~config ~resolve (Doctree.PageTitle.render_src_title sp)
578585
in
579586
if Config.as_json config then
580-
Html_fragment_json.make_src ~config ~url ~breadcrumbs [ doc ]
581-
else Html_page.make_src ~breadcrumbs ~header ~config ~url title [ doc ]
587+
Html_fragment_json.make_src ~config ~url ~breadcrumbs ~sidebar [ doc ]
588+
else
589+
Html_page.make_src ~breadcrumbs ~header ~config ~url ~sidebar title
590+
[ doc ]
582591
end
583592

584593
let render ~config ~sidebar = function
585594
| Document.Page page -> [ Page.page ~config ~sidebar page ]
586-
| Source_page src -> [ Page.source_page ~config src ]
595+
| Source_page src -> [ Page.source_page ~config ~sidebar src ]
587596

588597
let filepath ~config url = Link.Path.as_filename ~config url
589598

src/html/html_fragment_json.ml

Lines changed: 15 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,15 @@ let json_of_toc (toc : Types.toc list) : Json.json =
3030
let toc_json_list = toc |> List.map section in
3131
`Array toc_json_list
3232

33+
let json_of_html config h =
34+
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
35+
String.concat "" (List.map (Format.asprintf "%a" htmlpp) h)
36+
37+
let json_of_sidebar config sidebar =
38+
match sidebar with
39+
| None -> `Null
40+
| Some sidebar -> `String (json_of_html config sidebar)
41+
3342
let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
3443
~source_anchor content children =
3544
let filename = Link.Path.as_filename ~config url in
@@ -38,15 +47,7 @@ let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
3847
let source_anchor =
3948
match source_anchor with Some url -> `String url | None -> `Null
4049
in
41-
let json_of_html h =
42-
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
43-
String.concat "" (List.map (Format.asprintf "%a" htmlpp) h)
44-
in
45-
let global_toc =
46-
match sidebar with
47-
| None -> `Null
48-
| Some sidebar -> `String (json_of_html sidebar)
49-
in
50+
let global_toc = json_of_sidebar config sidebar in
5051
let content ppf =
5152
Format.pp_print_string ppf
5253
(json_to_string
@@ -58,24 +59,26 @@ let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
5859
("toc", json_of_toc toc);
5960
("global_toc", global_toc);
6061
("source_anchor", source_anchor);
61-
("preamble", `String (json_of_html preamble));
62-
("content", `String (json_of_html content));
62+
("preamble", `String (json_of_html config preamble));
63+
("content", `String (json_of_html config content));
6364
]))
6465
in
6566
{ Odoc_document.Renderer.filename; content; children; path = url }
6667

67-
let make_src ~config ~url ~breadcrumbs content =
68+
let make_src ~config ~url ~breadcrumbs ~sidebar content =
6869
let filename = Link.Path.as_filename ~config url in
6970
let filename = Fpath.add_ext ".json" filename in
7071
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
7172
let json_to_string json = Json.to_string json in
73+
let global_toc = json_of_sidebar config sidebar in
7274
let content ppf =
7375
Format.pp_print_string ppf
7476
(json_to_string
7577
(`Object
7678
[
7779
("type", `String "source");
7880
("breadcrumbs", json_of_breadcrumbs breadcrumbs);
81+
("global_toc", global_toc);
7982
( "content",
8083
`String
8184
(String.concat ""

src/html/html_fragment_json.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,5 +17,6 @@ val make_src :
1717
config:Config.t ->
1818
url:Odoc_document.Url.Path.t ->
1919
breadcrumbs:Types.breadcrumb list ->
20+
sidebar:Html_types.div_content Html.elt list option ->
2021
Html_types.div_content Html.elt list ->
2122
Odoc_document.Renderer.page

src/html/html_page.ml

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -258,7 +258,7 @@ let path_of_module_of_source ppf url =
258258
Format.fprintf ppf " (%s)" (String.concat "." path)
259259
| None -> ()
260260

261-
let src_page_creator ~breadcrumbs ~config ~url ~header name content =
261+
let src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar name content =
262262
let head : Html_types.head Html.elt =
263263
let title_string =
264264
Format.asprintf "Source: %s%a" name path_of_module_of_source url
@@ -269,6 +269,7 @@ let src_page_creator ~breadcrumbs ~config ~url ~header name content =
269269
let body =
270270
html_of_breadcrumbs breadcrumbs
271271
@ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ]
272+
@ sidebars ~global_toc:sidebar ~local_toc:[]
272273
@ content
273274
in
274275
(* We never indent as there is a bug in tyxml and it would break lines inside
@@ -284,9 +285,9 @@ let src_page_creator ~breadcrumbs ~config ~url ~header name content =
284285
in
285286
content
286287

287-
let make_src ~config ~url ~breadcrumbs ~header title content =
288+
let make_src ~config ~url ~breadcrumbs ~header ~sidebar title content =
288289
let filename = Link.Path.as_filename ~config url in
289290
let content =
290-
src_page_creator ~breadcrumbs ~config ~url ~header title content
291+
src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar title content
291292
in
292293
{ Odoc_document.Renderer.filename; content; children = []; path = url }

src/html/html_page.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ val make_src :
4040
url:Odoc_document.Url.Path.t ->
4141
breadcrumbs:Types.breadcrumb list ->
4242
header:Html_types.flow5_without_header_footer Html.elt list ->
43+
sidebar:Html_types.div_content Html.elt list option ->
4344
string ->
4445
Html_types.div_content Html.elt list ->
4546
Odoc_document.Renderer.page

src/html_support_files/odoc.css

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -340,7 +340,14 @@ nav.odoc-nav:has(+ .odoc-search:focus-within) {
340340
}
341341

342342
body.odoc-src {
343-
margin-right: calc(10vw + 20ex);
343+
display: grid;
344+
grid-template-columns: min-content 1fr;
345+
grid-template-areas:
346+
"search-bar nav "
347+
"toc-global preamble"
348+
"toc-global content ";
349+
column-gap: 4ex;
350+
grid-template-rows: auto auto 1fr;
344351
}
345352

346353
.odoc-content {
@@ -1362,6 +1369,7 @@ body.odoc:has( .odoc-search) .odoc-toc {
13621369

13631370
.source_container {
13641371
display: flex;
1372+
grid-area: content;
13651373
}
13661374

13671375
.source_line_column {

src/odoc/bin/main.ml

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -849,7 +849,7 @@ end = struct
849849
Arg.(
850850
value
851851
& opt (some convert_fpath) None
852-
& info [ "sidebar" ] ~doc ~docv:"FILE.odoc-index")
852+
& info [ "sidebar" ] ~doc ~docv:"FILE.odoc-sidebar")
853853

854854
let cmd =
855855
let syntax =
@@ -876,9 +876,10 @@ end = struct
876876

877877
module Generate_source = struct
878878
let generate extra output_dir syntax extra_suffix input_file
879-
warnings_options source_file =
879+
warnings_options source_file sidebar =
880880
Rendering.generate_source_odoc ~renderer:R.renderer ~warnings_options
881-
~syntax ~output:output_dir ~extra_suffix ~source_file extra input_file
881+
~syntax ~output:output_dir ~extra_suffix ~source_file ~sidebar extra
882+
input_file
882883

883884
let input_odocl =
884885
let doc = "Linked implementation file." in
@@ -903,10 +904,12 @@ end = struct
903904
& opt (pconv convert_syntax) Odoc_document.Renderer.OCaml
904905
@@ info ~docv:"SYNTAX" ~doc ~env [ "syntax" ])
905906
in
907+
let sidebar = Generate.sidebar in
906908
Term.(
907909
const handle_error
908910
$ (const generate $ R.extra_args $ dst ~create:true () $ syntax
909-
$ extra_suffix $ input_odocl $ warnings_options $ source_file))
911+
$ extra_suffix $ input_odocl $ warnings_options $ source_file $ sidebar
912+
))
910913

911914
let info ~docs =
912915
let doc =

0 commit comments

Comments
 (0)