Skip to content

Commit

Permalink
Sidebar: Add the global sidebar to implementation pages
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Nov 27, 2024
1 parent aabd040 commit a00a1ab
Show file tree
Hide file tree
Showing 12 changed files with 74 additions and 31 deletions.
12 changes: 10 additions & 2 deletions src/driver/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -300,9 +300,17 @@ let html_generate ~occurrence_file output_dir linked =
match l.kind with
| `Intf { hidden = true; _ } -> ()
| `Impl { src_path; _ } ->
Odoc.html_generate_source ~search_uris:[] ~output_dir ~input_file
let search_uris, sidebar =
match l.index with
| None -> (None, None)
| Some index ->
let db_path, sidebar = compile_index index in
let search_uris = [ db_path; Sherlodoc.js_file ] in
(Some search_uris, sidebar)
in
Odoc.html_generate_source ?search_uris ?sidebar ~output_dir ~input_file
~source:src_path ();
Odoc.html_generate_source ~search_uris:[] ~output_dir ~input_file
Odoc.html_generate_source ?search_uris ?sidebar ~output_dir ~input_file
~source:src_path ~as_json:true ();
Atomic.incr Stats.stats.generated_units
| `Asset ->
Expand Down
9 changes: 6 additions & 3 deletions src/driver/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -230,18 +230,21 @@ let html_generate_asset ~output_dir ?(ignore_output = false) ~input_file:file
in
ignore @@ Cmd_outputs.submit log desc cmd None

let html_generate_source ~output_dir ?(ignore_output = false) ~source
let html_generate_source ~output_dir ?(ignore_output = false) ~source ?sidebar
?(search_uris = []) ?(as_json = false) ~input_file:file () =
let open Cmd in
let file = v "--impl" % p file in
let sidebar =
match sidebar with None -> empty | Some idx -> v "--sidebar" % p idx
in
let search_uris =
List.fold_left
(fun acc filename -> acc % "--search-uri" % p filename)
empty search_uris
in
let cmd =
!odoc % "html-generate-source" %% file % p source %% search_uris % "-o"
% output_dir
!odoc % "html-generate-source" %% file %% sidebar % p source %% search_uris
% "-o" % output_dir
in
let cmd = if as_json then cmd % "--as-json" else cmd in

Expand Down
1 change: 1 addition & 0 deletions src/driver/odoc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,7 @@ val html_generate_source :
output_dir:string ->
?ignore_output:bool ->
source:Fpath.t ->
?sidebar:Fpath.t ->
?search_uris:Fpath.t list ->
?as_json:bool ->
input_file:Fpath.t ->
Expand Down
17 changes: 13 additions & 4 deletions src/html/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -567,23 +567,32 @@ module Page = struct
Html_page.make ~sidebar ~config ~header ~toc ~breadcrumbs ~url ~uses_katex
content subpages

and source_page ~config sp =
and source_page ~config ~sidebar sp =
let { Source_page.url; contents } = sp in
let resolve = Link.Current sp.url in
let sidebar =
match sidebar with
| None -> None
| Some sidebar ->
let sidebar = Odoc_document.Sidebar.to_block sidebar url in
(Some (block ~config ~resolve sidebar) :> any Html.elt list option)
in
let title = url.Url.Path.name
and doc = Html_source.html_of_doc ~config ~resolve contents in
let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~url in
let header =
items ~config ~resolve (Doctree.PageTitle.render_src_title sp)
in
if Config.as_json config then
Html_fragment_json.make_src ~config ~url ~breadcrumbs [ doc ]
else Html_page.make_src ~breadcrumbs ~header ~config ~url title [ doc ]
Html_fragment_json.make_src ~config ~url ~breadcrumbs ~sidebar [ doc ]
else
Html_page.make_src ~breadcrumbs ~header ~config ~url ~sidebar title
[ doc ]
end

let render ~config ~sidebar = function
| Document.Page page -> [ Page.page ~config ~sidebar page ]
| Source_page src -> [ Page.source_page ~config src ]
| Source_page src -> [ Page.source_page ~config ~sidebar src ]

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

Expand Down
27 changes: 15 additions & 12 deletions src/html/html_fragment_json.ml
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,15 @@ let json_of_toc (toc : Types.toc list) : Json.json =
let toc_json_list = toc |> List.map section in
`Array toc_json_list

let json_of_html config h =
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
String.concat "" (List.map (Format.asprintf "%a" htmlpp) h)

let json_of_sidebar config sidebar =
match sidebar with
| None -> `Null
| Some sidebar -> `String (json_of_html config sidebar)

let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
~source_anchor content children =
let filename = Link.Path.as_filename ~config url in
Expand All @@ -38,15 +47,7 @@ let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
let source_anchor =
match source_anchor with Some url -> `String url | None -> `Null
in
let json_of_html h =
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
String.concat "" (List.map (Format.asprintf "%a" htmlpp) h)
in
let global_toc =
match sidebar with
| None -> `Null
| Some sidebar -> `String (json_of_html sidebar)
in
let global_toc = json_of_sidebar config sidebar in
let content ppf =
Format.pp_print_string ppf
(json_to_string
Expand All @@ -58,24 +59,26 @@ let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
("toc", json_of_toc toc);
("global_toc", global_toc);
("source_anchor", source_anchor);
("preamble", `String (json_of_html preamble));
("content", `String (json_of_html content));
("preamble", `String (json_of_html config preamble));
("content", `String (json_of_html config content));
]))
in
{ Odoc_document.Renderer.filename; content; children; path = url }

let make_src ~config ~url ~breadcrumbs content =
let make_src ~config ~url ~breadcrumbs ~sidebar content =
let filename = Link.Path.as_filename ~config url in
let filename = Fpath.add_ext ".json" filename in
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
let json_to_string json = Json.to_string json in
let global_toc = json_of_sidebar config sidebar in
let content ppf =
Format.pp_print_string ppf
(json_to_string
(`Object
[
("type", `String "source");
("breadcrumbs", json_of_breadcrumbs breadcrumbs);
("global_toc", global_toc);
( "content",
`String
(String.concat ""
Expand Down
1 change: 1 addition & 0 deletions src/html/html_fragment_json.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,5 +17,6 @@ val make_src :
config:Config.t ->
url:Odoc_document.Url.Path.t ->
breadcrumbs:Types.breadcrumb list ->
sidebar:Html_types.div_content Html.elt list option ->
Html_types.div_content Html.elt list ->
Odoc_document.Renderer.page
7 changes: 4 additions & 3 deletions src/html/html_page.ml
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ let path_of_module_of_source ppf url =
Format.fprintf ppf " (%s)" (String.concat "." path)
| None -> ()

let src_page_creator ~breadcrumbs ~config ~url ~header name content =
let src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar name content =
let head : Html_types.head Html.elt =
let title_string =
Format.asprintf "Source: %s%a" name path_of_module_of_source url
Expand All @@ -269,6 +269,7 @@ let src_page_creator ~breadcrumbs ~config ~url ~header name content =
let body =
html_of_breadcrumbs breadcrumbs
@ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ]
@ sidebars ~global_toc:sidebar ~local_toc:[]
@ content
in
(* We never indent as there is a bug in tyxml and it would break lines inside
Expand All @@ -284,9 +285,9 @@ let src_page_creator ~breadcrumbs ~config ~url ~header name content =
in
content

let make_src ~config ~url ~breadcrumbs ~header title content =
let make_src ~config ~url ~breadcrumbs ~header ~sidebar title content =
let filename = Link.Path.as_filename ~config url in
let content =
src_page_creator ~breadcrumbs ~config ~url ~header title content
src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar title content
in
{ Odoc_document.Renderer.filename; content; children = []; path = url }
1 change: 1 addition & 0 deletions src/html/html_page.mli
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ val make_src :
url:Odoc_document.Url.Path.t ->
breadcrumbs:Types.breadcrumb list ->
header:Html_types.flow5_without_header_footer Html.elt list ->
sidebar:Html_types.div_content Html.elt list option ->
string ->
Html_types.div_content Html.elt list ->
Odoc_document.Renderer.page
Expand Down
10 changes: 9 additions & 1 deletion src/html_support_files/odoc.css
Original file line number Diff line number Diff line change
Expand Up @@ -340,7 +340,14 @@ nav.odoc-nav:has(+ .odoc-search:focus-within) {
}

body.odoc-src {
margin-right: calc(10vw + 20ex);
display: grid;
grid-template-columns: min-content 1fr;
grid-template-areas:
"search-bar nav "
"toc-global preamble"
"toc-global content ";
column-gap: 4ex;
grid-template-rows: auto auto 1fr;
}

.odoc-content {
Expand Down Expand Up @@ -1362,6 +1369,7 @@ body.odoc:has( .odoc-search) .odoc-toc {

.source_container {
display: flex;
grid-area: content;
}

.source_line_column {
Expand Down
11 changes: 7 additions & 4 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -849,7 +849,7 @@ end = struct
Arg.(
value
& opt (some convert_fpath) None
& info [ "sidebar" ] ~doc ~docv:"FILE.odoc-index")
& info [ "sidebar" ] ~doc ~docv:"FILE.odoc-sidebar")

let cmd =
let syntax =
Expand All @@ -876,9 +876,10 @@ end = struct

module Generate_source = struct
let generate extra output_dir syntax extra_suffix input_file
warnings_options source_file =
warnings_options source_file sidebar =
Rendering.generate_source_odoc ~renderer:R.renderer ~warnings_options
~syntax ~output:output_dir ~extra_suffix ~source_file extra input_file
~syntax ~output:output_dir ~extra_suffix ~source_file ~sidebar extra
input_file

let input_odocl =
let doc = "Linked implementation file." in
Expand All @@ -903,10 +904,12 @@ end = struct
& opt (pconv convert_syntax) Odoc_document.Renderer.OCaml
@@ info ~docv:"SYNTAX" ~doc ~env [ "syntax" ])
in
let sidebar = Generate.sidebar in
Term.(
const handle_error
$ (const generate $ R.extra_args $ dst ~create:true () $ syntax
$ extra_suffix $ input_odocl $ warnings_options $ source_file))
$ extra_suffix $ input_odocl $ warnings_options $ source_file $ sidebar
))

let info ~docs =
let doc =
Expand Down
8 changes: 6 additions & 2 deletions src/odoc/rendering.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,14 +93,18 @@ let documents_of_implementation ~warnings_options:_ ~syntax impl source_file =
Error (`Msg "The implementation unit was not compiled with --source-id.")

let generate_source_odoc ~syntax ~warnings_options ~renderer ~output
~source_file ~extra_suffix extra file =
~source_file ~extra_suffix ~sidebar extra file =
Odoc_file.load file >>= fun unit ->
(match sidebar with
| None -> Ok None
| Some x -> Odoc_file.load_sidebar x >>= fun sidebar -> Ok (Some sidebar))
>>= fun sidebar ->
match unit.content with
| Odoc_file.Impl_content impl ->
documents_of_implementation ~warnings_options ~syntax impl source_file
>>= fun docs ->
List.iter
(render_document renderer ~output ~sidebar:None ~extra_suffix ~extra)
(render_document renderer ~output ~sidebar ~extra_suffix ~extra)
docs;
Ok ()
| Page_content _ | Unit_content _ | Asset_content _ ->
Expand Down
1 change: 1 addition & 0 deletions src/odoc/rendering.mli
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ val generate_source_odoc :
output:Fs.directory ->
source_file:Fpath.t ->
extra_suffix:string option ->
sidebar:Fpath.t option ->
'a ->
Fpath.t ->
(unit, [> msg ]) result
Expand Down

0 comments on commit a00a1ab

Please sign in to comment.