Skip to content

Commit

Permalink
Sidebar: separate its generation pipeline from main doc
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Jul 4, 2024
1 parent a61456e commit 068d8ec
Show file tree
Hide file tree
Showing 13 changed files with 161 additions and 298 deletions.
5 changes: 2 additions & 3 deletions src/document/ML.mli
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,9 @@

open Odoc_model

val compilation_unit :
?sidebar:Lang.Sidebar.t -> Lang.Compilation_unit.t -> Types.Document.t
val compilation_unit : Lang.Compilation_unit.t -> Types.Document.t

val page : ?sidebar:Lang.Sidebar.t -> Lang.Page.t -> Types.Document.t
val page : Lang.Page.t -> Types.Document.t
(** Convert compilation unit or page models into a document *)

val source_tree : Lang.SourceTree.t -> Types.Document.t list
Expand Down
344 changes: 95 additions & 249 deletions src/document/generator.ml

Large diffs are not rendered by default.

5 changes: 2 additions & 3 deletions src/document/generator_signatures.ml
Original file line number Diff line number Diff line change
Expand Up @@ -102,10 +102,9 @@ module type SYNTAX = sig
end

module type GENERATOR = sig
val compilation_unit :
?sidebar:Lang.Sidebar.t -> Lang.Compilation_unit.t -> Document.t
val compilation_unit : Lang.Compilation_unit.t -> Document.t

val page : ?sidebar:Lang.Sidebar.t -> Lang.Page.t -> Document.t
val page : Lang.Page.t -> Document.t

val source_tree : Lang.SourceTree.t -> Document.t list

Expand Down
5 changes: 2 additions & 3 deletions src/document/reason.mli
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,9 @@

open Odoc_model

val compilation_unit :
?sidebar:Lang.Sidebar.t -> Lang.Compilation_unit.t -> Types.Document.t
val compilation_unit : Lang.Compilation_unit.t -> Types.Document.t

val page : ?sidebar:Lang.Sidebar.t -> Lang.Page.t -> Types.Document.t
val page : Lang.Page.t -> Types.Document.t
(** Convert compilation unit or page models into a document *)

val source_tree : Lang.SourceTree.t -> Types.Document.t list
Expand Down
14 changes: 6 additions & 8 deletions src/document/renderer.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,14 +23,12 @@ type input =

type 'a t = {
name : string;
render : 'a -> Types.Document.t -> page list;
render : 'a -> Types.Block.t option -> Types.Document.t -> page list;
extra_documents : 'a -> input -> Types.Document.t list;
}

let document_of_page ~syntax ?sidebar v =
match syntax with
| Reason -> Reason.page ?sidebar v
| OCaml -> ML.page ?sidebar v
let document_of_page ~syntax v =
match syntax with Reason -> Reason.page v | OCaml -> ML.page v

let documents_of_source_tree ~syntax v =
match syntax with Reason -> Reason.source_tree v | OCaml -> ML.source_tree v
Expand All @@ -40,7 +38,7 @@ let documents_of_implementation ~syntax v =
| Reason -> Reason.implementation v
| OCaml -> ML.implementation v

let document_of_compilation_unit ~syntax ?sidebar v =
let document_of_compilation_unit ~syntax v =
match syntax with
| Reason -> Reason.compilation_unit ?sidebar v
| OCaml -> ML.compilation_unit ?sidebar v
| Reason -> Reason.compilation_unit v
| OCaml -> ML.compilation_unit v
1 change: 0 additions & 1 deletion src/document/types.ml
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,6 @@ and Page : sig
type t = {
preamble : Item.t list;
items : Item.t list;
sidebar : Block.t option;
url : Url.Path.t;
source_anchor : Url.t option;
(** Url to the corresponding source code. Might be a whole source file
Expand Down
20 changes: 12 additions & 8 deletions src/html/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -482,20 +482,24 @@ module Page = struct
| `Closed | `Open | `Default -> None
| `Inline -> Some 0)

let rec include_ ~config { Subpage.content; _ } = page ~config content
let rec include_ ~config ~sidebar { Subpage.content; _ } =
page ~config ~sidebar content

and subpages ~config subpages = List.map (include_ ~config) subpages
and subpages ~config ~sidebar subpages =
List.map (include_ ~config ~sidebar) subpages

and page ~config p : Odoc_document.Renderer.page =
let { Page.preamble; items = i; url; source_anchor; sidebar } =
and page ~config ~sidebar p : Odoc_document.Renderer.page =
let { Page.preamble; items = i; url; source_anchor } =
Doctree.Labels.disambiguate_page ~enter_subpages:false p
in
let subpages = subpages ~config @@ Doctree.Subpages.compute p in
let subpages = subpages ~config ~sidebar @@ Doctree.Subpages.compute p in
let resolve = Link.Current url in
let sidebar =
match sidebar with
| None -> None
| Some x -> (Some (block ~config ~resolve x) :> any Html.elt list option)
| Some sidebar ->
(* let sidebar = Odoc_document.Sidebar.to_block sidebar p in *)
(Some (block ~config ~resolve sidebar) :> any Html.elt list option)
in
let i = Doctree.Shift.compute ~on_sub i in
let uses_katex = Doctree.Math.has_math_elements p in
Expand Down Expand Up @@ -553,8 +557,8 @@ module Page = struct
{ Odoc_document.Renderer.filename; content; children = [] }
end

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

Expand Down
1 change: 1 addition & 0 deletions src/html/generator.mli
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
val render :
config:Config.t ->
sidebar:Odoc_document.Types.Block.t option ->
Odoc_document.Types.Document.t ->
Odoc_document.Renderer.page list

Expand Down
4 changes: 2 additions & 2 deletions src/odoc/html_page.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,8 @@ open Odoc_model

type args = { html_config : Odoc_html.Config.t; assets : Fpath.t list }

let render { html_config; assets = _ } page =
Odoc_html.Generator.render ~config:html_config page
let render { html_config; assets = _ } sidebar page =
Odoc_html.Generator.render ~config:html_config ~sidebar page

let list_filter_map f lst =
List.rev
Expand Down
2 changes: 1 addition & 1 deletion src/odoc/latex.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ open Odoc_document

type args = { with_children : bool }

let render args page =
let render args _sidebar page =
Odoc_latex.Generator.render ~with_children:args.with_children page

let extra_documents _args _unit = []
Expand Down
2 changes: 1 addition & 1 deletion src/odoc/man_page.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
open Odoc_document

let render _ page = Odoc_manpage.Generator.render page
let render _ _sidebar page = Odoc_manpage.Generator.render page

let extra_documents _args _unit = []

Expand Down
53 changes: 34 additions & 19 deletions src/odoc/rendering.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
module Sidebar_ = Sidebar
open Odoc_document
module Sidebar = Sidebar_
open Or_error
open Odoc_model

Expand All @@ -23,22 +25,21 @@ let check_empty_source_arg source filename =
filename

let documents_of_unit ~warnings_options ~syntax ~source ~renderer ~extra
~filename ?sidebar unit =
~filename unit =
Error.catch_warnings (fun () ->
check_empty_source_arg source filename;
renderer.Renderer.extra_documents extra (CU unit))
|> Error.handle_warnings ~warnings_options
>>= fun extra_docs ->
Ok (Renderer.document_of_compilation_unit ?sidebar ~syntax unit :: extra_docs)
Ok (Renderer.document_of_compilation_unit ~syntax unit :: extra_docs)

let documents_of_page ~warnings_options ~syntax ~source ~renderer ~extra
~filename ?sidebar page =
~filename page =
Error.catch_warnings (fun () ->
check_empty_source_arg source filename;
renderer.Renderer.extra_documents extra (Page page))
|> Error.handle_warnings ~warnings_options
>>= fun extra_docs ->
Ok (Renderer.document_of_page ~syntax ?sidebar page :: extra_docs)
>>= fun extra_docs -> Ok (Renderer.document_of_page ~syntax page :: extra_docs)

let documents_of_implementation ~warnings_options:_ ~syntax impl source =
match (source, impl.Lang.Implementation.id) with
Expand Down Expand Up @@ -83,23 +84,22 @@ let documents_of_source_tree ~warnings_options ~syntax ~source ~filename srctree
|> Error.handle_warnings ~warnings_options
>>= fun () -> Ok (Renderer.documents_of_source_tree ~syntax srctree)

let documents_of_odocl ~warnings_options ~renderer ~extra ~source ~syntax
?sidebar input =
let documents_of_odocl ~warnings_options ~renderer ~extra ~source ~syntax input
=
Odoc_file.load input >>= fun unit ->
let filename = Fpath.to_string input in
match unit.content with
| Odoc_file.Page_content odoctree ->
documents_of_page ~warnings_options ~syntax ~source ~renderer ~extra
~filename ?sidebar odoctree
~filename odoctree
| Source_tree_content srctree ->
documents_of_source_tree ~warnings_options ~syntax ~source ~filename
srctree
| Impl_content impl ->
documents_of_implementation ~warnings_options ~syntax (* ?sidebar *) impl
source
documents_of_implementation ~warnings_options ~syntax impl source
| Unit_content odoctree ->
documents_of_unit ~warnings_options ~source ~syntax ~renderer ~extra
~filename ?sidebar odoctree
~filename odoctree

let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
input =
Expand All @@ -112,8 +112,18 @@ let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
documents_of_unit ~warnings_options ~source:None ~filename:"" ~syntax
~renderer ~extra m

let render_document renderer ~output:root_dir ~extra_suffix ~extra doc =
let pages = renderer.Renderer.render extra doc in
let render_document renderer ~sidebar ~output:root_dir ~extra_suffix ~extra doc
=
let url =
match doc with
| Odoc_document.Types.Document.Page { url; _ } -> url
| Source_page { url; _ } -> url
| Asset { url; _ } -> url
in
let sidebar =
Option.map (fun sb -> Odoc_document.Sidebar.to_block sb url) sidebar
in
let pages = renderer.Renderer.render extra sidebar doc in
Renderer.traverse pages ~f:(fun filename content ->
let filename =
match extra_suffix with
Expand All @@ -133,18 +143,23 @@ let render_odoc ~resolver ~warnings_options ~syntax ~renderer ~output extra file
let extra_suffix = None in
documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax file
>>= fun docs ->
List.iter (render_document renderer ~output ~extra_suffix ~extra) docs;
List.iter
(render_document renderer ~sidebar:None ~output ~extra_suffix ~extra)
docs;
Ok ()

let generate_odoc ~syntax ~warnings_options ~renderer ~output ~extra_suffix
~source ~sidebar extra file =
let sidebar =
match sidebar with None -> None | Some x -> Some (Sidebar.read x)
match sidebar with
| None -> None
| Some x -> Some (x |> Sidebar.read |> Odoc_document.Sidebar.of_lang)
in
documents_of_odocl ~warnings_options ~renderer ~source ~extra ~syntax ?sidebar
file
documents_of_odocl ~warnings_options ~renderer ~source ~extra ~syntax file
>>= fun docs ->
List.iter (render_document renderer ~output ~extra_suffix ~extra) docs;
List.iter
(render_document renderer ~output ~sidebar ~extra_suffix ~extra)
docs;
Ok ()

let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir
Expand All @@ -160,7 +175,7 @@ let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir
docs >>= fun docs ->
List.iter
(fun doc ->
let pages = renderer.Renderer.render extra doc in
let pages = renderer.Renderer.render extra None doc in
Renderer.traverse pages ~f:(fun filename _content ->
let filename = Fpath.normalize @@ Fs.File.append root_dir filename in
Format.printf "%a\n" Fpath.pp filename))
Expand Down
3 changes: 3 additions & 0 deletions test/parent_id/sidebar.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -54,3 +54,6 @@
<ul><li><a href="#" class="current_unit">Unit</a></li></ul>
</li>
</ul>

$ odoc support-files -o html
$ cp -r html /tmp/html

0 comments on commit 068d8ec

Please sign in to comment.