diff --git a/src/document/breadcrumbs.ml b/src/document/breadcrumbs.ml new file mode 100644 index 0000000000..bd1c4ccf82 --- /dev/null +++ b/src/document/breadcrumbs.ml @@ -0,0 +1,40 @@ +open Odoc_model +open Names +module Id = Paths.Identifier + +type t = (string * Url.Path.t) list + +let empty = [] + +let of_lang ~index id = + let module H = Id.Hashtbl.Page in + let mk_seg id title = + (title, Url.Path.from_identifier (id :> Url.Path.any)) + in + let mk_page_seg id title = + let title = + match index with + | Some index -> ( + try H.find index.Lang.Index.pages_short_title (id :> Id.Page.t) + with Not_found -> title) + | None -> title + in + mk_seg id title + in + let rec of_page acc id = + match id.Id.iv with + | `Page (parent, pname) -> + of_parent (mk_page_seg id (PageName.to_string pname) :: acc) parent + and of_parent acc = function Some p -> of_page acc p | None -> acc in + let of_odocid (id : Id.OdocId.t) = + match id with + | { Id.iv = #Id.ContainerPage.t_pv; _ } as id -> of_page [] id + | { iv = `LeafPage (parent, pname); _ } as id -> + of_parent [ mk_page_seg id (PageName.to_string pname) ] parent + | { iv = `Root (parent, mname); _ } as id -> + of_parent [ mk_seg id (ModuleName.to_string mname) ] parent + | { iv = `SourcePage (parent, name); _ } as id -> + of_page [ mk_seg id ("Source " ^ name) ] parent + | { iv = `Implementation _ | `AssetFile _; _ } -> [] + in + of_odocid id diff --git a/src/document/breadcrumbs.mli b/src/document/breadcrumbs.mli new file mode 100644 index 0000000000..01f4544f6a --- /dev/null +++ b/src/document/breadcrumbs.mli @@ -0,0 +1,10 @@ +open Odoc_model +module Id = Paths.Identifier + +type t = (string * Url.Path.t) list + +val empty : t + +val of_lang : index:'a Lang.Index.t option -> Id.OdocId.t -> t +(** Compute the breadcrumbs for the current unit. If [index] is not [None], + it's used to retrieve the short titles of pages. *) diff --git a/src/document/renderer.ml b/src/document/renderer.ml index 270f70292d..b4bde05ba6 100644 --- a/src/document/renderer.ml +++ b/src/document/renderer.ml @@ -23,7 +23,12 @@ type input = type 'a t = { name : string; - render : 'a -> Types.Block.t option -> Types.Document.t -> page list; + render : + 'a -> + sidebar:Types.Block.t option -> + breadcrumbs:Breadcrumbs.t -> + Types.Document.t -> + page list; filepath : 'a -> Url.Path.t -> Fpath.t; } diff --git a/src/html/generator.ml b/src/html/generator.ml index b40f90b16d..6e78d839bf 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -13,6 +13,7 @@ * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_utils module HLink = Link open Odoc_document.Types module Html = Tyxml.Html @@ -498,24 +499,30 @@ end module Breadcrumbs = struct open Types - let gen_breadcrumbs ~config ~url = - let rec get_parent_paths x = - match x with - | [] -> [] - | x :: xs -> ( - match Odoc_document.Url.Path.of_list (List.rev (x :: xs)) with - | Some x -> x :: get_parent_paths xs - | None -> get_parent_paths xs) + let gen_breadcrumbs ~config ~current_url breadcrumbs = + let resolve = Link.Current current_url in + let mk url name = + let href = Link.href ~config ~resolve (Url.from_path url) in + { href; name; kind = url.kind } in - let to_breadcrumb path = - let href = - Link.href ~config ~resolve:(Current url) - (Odoc_document.Url.from_path path) - in - { href; name = path.name; kind = path.kind } + let is_local_breadcrumb = + match breadcrumbs with + | [] -> fun _ -> true + | _ :: _ -> + let _, last_page_seg = List.last breadcrumbs in + ( <> ) last_page_seg + in + let rec local_breadcrumbs acc url = + if is_local_breadcrumb url then parent (mk url url.name :: acc) url.parent + else acc + and parent acc = function + | Some p -> local_breadcrumbs acc p + | None -> acc + in + let page_breadcrumbs = + List.rev_map (fun (title, url) -> mk url title) breadcrumbs in - get_parent_paths (List.rev (Odoc_document.Url.Path.to_list url)) - |> List.rev |> List.map to_breadcrumb + List.rev_append page_breadcrumbs (local_breadcrumbs [] current_url) end module Page = struct @@ -526,17 +533,19 @@ module Page = struct | `Closed | `Open | `Default -> None | `Inline -> Some 0) - let rec include_ ~config ~sidebar { Subpage.content; _ } = - page ~config ~sidebar content + let rec include_ ~config ~sidebar ~breadcrumbs { Subpage.content; _ } = + page ~config ~sidebar ~breadcrumbs content - and subpages ~config ~sidebar subpages = - List.map (include_ ~config ~sidebar) subpages + and subpages ~config ~sidebar ~breadcrumbs subpages = + List.map (include_ ~config ~sidebar ~breadcrumbs) subpages - and page ~config ~sidebar p : Odoc_document.Renderer.page = + and page ~config ~sidebar ~breadcrumbs 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 ~sidebar @@ Doctree.Subpages.compute p in + let subpages = + subpages ~config ~sidebar ~breadcrumbs @@ Doctree.Subpages.compute p + in let resolve = Link.Current url in let sidebar = match sidebar with @@ -548,7 +557,9 @@ module Page = struct let i = Doctree.Shift.compute ~on_sub i in let uses_katex = Doctree.Math.has_math_elements p in let toc = Toc.gen_toc ~config ~resolve ~path:url i in - let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~url in + let breadcrumbs = + Breadcrumbs.gen_breadcrumbs ~config ~current_url:url breadcrumbs + in let content = (items ~config ~resolve i :> any Html.elt list) in if Config.as_json config then let source_anchor = @@ -567,12 +578,14 @@ 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 ~breadcrumbs sp = let { Source_page.url; contents } = sp in let resolve = Link.Current sp.url 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 breadcrumbs = + Breadcrumbs.gen_breadcrumbs ~config ~current_url:url breadcrumbs + in let header = items ~config ~resolve (Doctree.PageTitle.render_src_title sp) in @@ -581,9 +594,9 @@ module Page = struct else Html_page.make_src ~breadcrumbs ~header ~config ~url title [ doc ] end -let render ~config ~sidebar = function - | Document.Page page -> [ Page.page ~config ~sidebar page ] - | Source_page src -> [ Page.source_page ~config src ] +let render ~config ~sidebar ~breadcrumbs = function + | Document.Page page -> [ Page.page ~config ~sidebar ~breadcrumbs page ] + | Source_page src -> [ Page.source_page ~config ~breadcrumbs src ] let filepath ~config url = Link.Path.as_filename ~config url diff --git a/src/html/generator.mli b/src/html/generator.mli index 446d2346f7..81d3755a19 100644 --- a/src/html/generator.mli +++ b/src/html/generator.mli @@ -1,13 +1,16 @@ +open Odoc_document + val render : config:Config.t -> - sidebar:Odoc_document.Types.Block.t option -> - Odoc_document.Types.Document.t -> - Odoc_document.Renderer.page list + sidebar:Types.Block.t option -> + breadcrumbs:Breadcrumbs.t -> + Types.Document.t -> + Renderer.page list -val filepath : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t +val filepath : config:Config.t -> Url.Path.t -> Fpath.t val doc : config:Config.t -> xref_base_uri:string -> - Odoc_document.Types.Block.t -> + Types.Block.t -> Html_types.flow5_without_sectioning_heading_header_footer Tyxml.Html.elt list diff --git a/src/model/frontmatter.ml b/src/model/frontmatter.ml index f50e98da1b..5517a643f0 100644 --- a/src/model/frontmatter.ml +++ b/src/model/frontmatter.ml @@ -1 +1,3 @@ type t = (string * string) list + +let get = List.assoc_opt diff --git a/src/model/lang.ml b/src/model/lang.ml index 4715481536..655568edb4 100644 --- a/src/model/lang.ml +++ b/src/model/lang.ml @@ -551,10 +551,13 @@ module rec Sidebar : sig end = Sidebar -module rec Index : sig - type 'a t = Sidebar.t * 'a Paths.Identifier.Hashtbl.Any.t -end = - Index +module Index = struct + type 'a t = { + sidebar : Sidebar.t; + entries : 'a Paths.Identifier.Hashtbl.Any.t; + pages_short_title : string Paths.Identifier.Hashtbl.Page.t; + } +end module rec Asset : sig type t = { name : Identifier.AssetFile.t; root : Root.t } diff --git a/src/model/odoc_model.ml b/src/model/odoc_model.ml index f81a5fe1a7..43965ad14a 100644 --- a/src/model/odoc_model.ml +++ b/src/model/odoc_model.ml @@ -10,3 +10,4 @@ module Location_ = Location_ module Compat = Compat module Semantics = Semantics module Reference = Reference +module Frontmatter = Frontmatter diff --git a/src/model/paths.ml b/src/model/paths.ml index e055b0202e..1f893b08a2 100644 --- a/src/model/paths.ml +++ b/src/model/paths.ml @@ -361,6 +361,8 @@ module Identifier = struct module Page = struct type t = Id.page type t_pv = Id.page_pv + let equal = equal + let hash = hash end module ContainerPage = struct @@ -623,6 +625,7 @@ module Identifier = struct module Hashtbl = struct module Any = Hashtbl.Make (Any) + module Page = Hashtbl.Make (Page) end end diff --git a/src/model/paths.mli b/src/model/paths.mli index bca68307d2..7a9644e7ea 100644 --- a/src/model/paths.mli +++ b/src/model/paths.mli @@ -235,6 +235,7 @@ module Identifier : sig module Hashtbl : sig module Any : Hashtbl.S with type key = Any.t + module Page : Hashtbl.S with type key = Page.t end module Mk : sig diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index e9936c3271..e9c378f3e4 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -644,11 +644,13 @@ end = struct | None -> Ok detected_package let current_package_of_page ~current_package page_roots input = - match find_root_of_input page_roots input with - | Ok detected_package -> - validate_current_package ?detected_package page_roots current_package - | Error `Not_found -> - Error (`Msg "The output file must be part of a directory passed as -P") + let detected_package = + (* Driver generated pages might not belong to a doc hierarchy. *) + match find_root_of_input page_roots input with + | Ok p -> p + | Error `Not_found -> None + in + validate_current_package ?detected_package page_roots current_package let is_page input = input |> Fpath.filename |> Astring.String.is_prefix ~affix:"page-" diff --git a/src/odoc/html_page.ml b/src/odoc/html_page.ml index 01e2de2ccc..f8b90198f4 100644 --- a/src/odoc/html_page.ml +++ b/src/odoc/html_page.ml @@ -16,8 +16,8 @@ type args = { html_config : Odoc_html.Config.t } -let render { html_config } sidebar page = - Odoc_html.Generator.render ~config:html_config ~sidebar page +let render { html_config } ~sidebar ~breadcrumbs page = + Odoc_html.Generator.render ~config:html_config ~sidebar ~breadcrumbs page let filepath { html_config } url = Odoc_html.Generator.filepath ~config:html_config url diff --git a/src/odoc/indexing.ml b/src/odoc/indexing.ml index 086315f96f..4312b5bc8e 100644 --- a/src/odoc/indexing.ml +++ b/src/odoc/indexing.ml @@ -3,12 +3,10 @@ open Odoc_json_index open Or_error open Odoc_model -module H = Odoc_model.Paths.Identifier.Hashtbl.Any - let handle_file file ~unit ~page ~occ = match Fpath.basename file with | s when String.is_prefix ~affix:"index-" s -> - Odoc_file.load_index file >>= fun (_sidebar, index) -> Ok (occ index) + Odoc_file.load_index file >>= fun index -> Ok (occ index.entries) | _ -> ( Odoc_file.load file >>= fun unit' -> match unit' with @@ -74,10 +72,12 @@ let compile_to_json ~output ~warnings_options ~occurrences files = Format.fprintf output "]"; Ok () -let compile_to_marshall ~output ~warnings_options sidebar files = +let compile_to_marshall ~output ~warnings_options ~pages_short_title sidebar + files = + let module H = Paths.Identifier.Hashtbl.Any in let final_index = H.create 10 in let unit u = - Odoc_model.Fold.unit + Fold.unit ~f:(fun () item -> let entries = Odoc_search.Entry.entries_of_item item in List.iter @@ -86,7 +86,7 @@ let compile_to_marshall ~output ~warnings_options sidebar files = () u in let page p = - Odoc_model.Fold.page + Fold.page ~f:(fun () item -> let entries = Odoc_search.Entry.entries_of_item item in List.iter @@ -108,14 +108,17 @@ let compile_to_marshall ~output ~warnings_options sidebar files = in let result = Error.catch_warnings index in result |> Error.handle_warnings ~warnings_options >>= fun () -> - Ok (Odoc_file.save_index output (sidebar, final_index)) + let index = + { Lang.Index.sidebar; entries = final_index; pages_short_title } + in + Ok (Odoc_file.save_index output index) let read_occurrences file = let ic = open_in_bin file in let htbl : Odoc_occurrences.Table.t = Marshal.from_channel ic in htbl -open Odoc_model.Lang.Sidebar +open Lang.Sidebar let compile out_format ~output ~warnings_options ~occurrences ~lib_roots ~page_roots ~inputs_in_file ~odocls = @@ -142,20 +145,24 @@ let compile out_format ~output ~warnings_options ~occurrences ~lib_roots in (* if files = [] && then Error (`Msg "No .odocl files were included") *) (* else *) - let pages = + let all_pages_of_roots = List.map (fun (page_root, _) -> - let pages = Resolver.all_pages ~root:page_root resolver in + (page_root, Resolver.all_pages ~root:page_root resolver)) + page_roots + in + let pages = + List.map + (fun (page_root, pages) -> let pages = List.map - (fun (page_id, title) -> + (fun (page_id, page_info) -> let title = - match title with + match page_info.Root.Odoc_file.title with | None -> [ - Odoc_model.Location_.at - (Odoc_model.Location_.span []) - (`Word (Odoc_model.Paths.Identifier.name page_id)); + Location_.at (Location_.span []) + (`Word (Paths.Identifier.name page_id)); ] | Some x -> x in @@ -163,7 +170,7 @@ let compile out_format ~output ~warnings_options ~occurrences ~lib_roots pages in { page_name = page_root; pages }) - page_roots + all_pages_of_roots in let libraries = List.map @@ -183,7 +190,25 @@ let compile out_format ~output ~warnings_options ~occurrences ~lib_roots [] include_rec) |> List.concat) in + let pages_short_title = + let module H = Odoc_model.Paths.Identifier.Hashtbl.Page in + let dst = H.create 8 in + List.iter + (fun (_, pages) -> + List.iter + (fun (id, page_info) -> + match + Frontmatter.get "short_title" page_info.Root.Odoc_file.frontmatter + with + | Some short_title -> H.replace dst id short_title + | None -> ()) + pages) + all_pages_of_roots; + dst + in let content = { pages; libraries } in match out_format with | `JSON -> compile_to_json ~output ~warnings_options ~occurrences files - | `Marshall -> compile_to_marshall ~output ~warnings_options content files + | `Marshall -> + compile_to_marshall ~output ~warnings_options ~pages_short_title content + files diff --git a/src/odoc/latex.ml b/src/odoc/latex.ml index 78e1d621f5..9b0ae08b8f 100644 --- a/src/odoc/latex.ml +++ b/src/odoc/latex.ml @@ -2,7 +2,7 @@ open Odoc_document type args = { with_children : bool } -let render args _sidebar page = +let render args ~sidebar:_ ~breadcrumbs:_ page = Odoc_latex.Generator.render ~with_children:args.with_children page let filepath _args url = Odoc_latex.Generator.filepath url diff --git a/src/odoc/man_page.ml b/src/odoc/man_page.ml index 95e4a26814..d1e384b5a4 100644 --- a/src/odoc/man_page.ml +++ b/src/odoc/man_page.ml @@ -1,6 +1,6 @@ open Odoc_document -let render _ _sidebar page = Odoc_manpage.Generator.render page +let render _ ~sidebar:_ ~breadcrumbs:_ page = Odoc_manpage.Generator.render page let filepath _ url = Odoc_manpage.Generator.filepath url diff --git a/src/odoc/rendering.ml b/src/odoc/rendering.ml index b373203b4e..6027be4545 100644 --- a/src/odoc/rendering.ml +++ b/src/odoc/rendering.ml @@ -1,6 +1,8 @@ +open Odoc_utils open Odoc_document open Or_error open Odoc_model +module Id = Paths.Identifier let prepare ~extra_suffix ~output_dir filename = let filename = @@ -17,9 +19,13 @@ let document_of_odocl ~syntax input = Odoc_file.load input >>= fun unit -> match unit.content with | Odoc_file.Page_content odoctree -> - Ok (Renderer.document_of_page ~syntax odoctree) + Ok + ( (odoctree.name :> Id.OdocId.t), + Renderer.document_of_page ~syntax odoctree ) | Unit_content odoctree -> - Ok (Renderer.document_of_compilation_unit ~syntax odoctree) + Ok + ( (odoctree.id :> Id.OdocId.t), + Renderer.document_of_compilation_unit ~syntax odoctree ) | Impl_content _ -> Error (`Msg @@ -34,8 +40,10 @@ let document_of_odocl ~syntax input = let document_of_input ~resolver ~warnings_options ~syntax input = let output = Fs.File.(set_ext ".odocl" input) in Odoc_link.from_odoc ~resolver ~warnings_options input output >>= function - | `Page page -> Ok (Renderer.document_of_page ~syntax page) - | `Module m -> Ok (Renderer.document_of_compilation_unit ~syntax m) + | `Page page -> + Ok ((page.name :> Id.OdocId.t), Renderer.document_of_page ~syntax page) + | `Module m -> + Ok ((m.id :> Id.OdocId.t), Renderer.document_of_compilation_unit ~syntax m) | `Impl _ -> Error (`Msg @@ -47,19 +55,17 @@ let document_of_input ~resolver ~warnings_options ~syntax input = "Wrong kind of unit: Expected a page or module unit, got an asset \ unit. Use the dedicated command for assets.") -let render_document renderer ~sidebar ~output:root_dir ~extra_suffix ~extra doc - = +let render_document renderer ~sidebar ~breadcrumbs ~output:root_dir + ~extra_suffix ~extra doc = let url = match doc with | Odoc_document.Types.Document.Page { url; _ } -> url | Source_page { url; _ } -> url in let sidebar = - Odoc_utils.Option.map - (fun sb -> Odoc_document.Sidebar.to_block sb url) - sidebar + Option.map (fun sb -> Odoc_document.Sidebar.to_block sb url) sidebar in - let pages = renderer.Renderer.render extra sidebar doc in + let pages = renderer.Renderer.render extra ~sidebar ~breadcrumbs doc in Renderer.traverse pages ~f:(fun filename content -> let filename = prepare ~extra_suffix ~output_dir:root_dir filename in let oc = open_out (Fs.File.to_string filename) in @@ -70,20 +76,26 @@ let render_document renderer ~sidebar ~output:root_dir ~extra_suffix ~extra doc let render_odoc ~resolver ~warnings_options ~syntax ~renderer ~output extra file = let extra_suffix = None in - document_of_input ~resolver ~warnings_options ~syntax file >>= fun doc -> - render_document renderer ~sidebar:None ~output ~extra_suffix ~extra doc; + document_of_input ~resolver ~warnings_options ~syntax file + >>= fun (id, doc) -> + let breadcrumbs = Odoc_document.Breadcrumbs.of_lang ~index:None id in + render_document renderer ~sidebar:None ~breadcrumbs ~output ~extra_suffix + ~extra doc; Ok () let generate_odoc ~syntax ~warnings_options:_ ~renderer ~output ~extra_suffix ~sidebar extra file = + document_of_odocl ~syntax file >>= fun (id, doc) -> (match sidebar with - | None -> Ok None + | None -> Ok (None, None) | Some x -> - Odoc_file.load_index x >>= fun (sidebar, _) -> - Ok (Some (Odoc_document.Sidebar.of_lang sidebar))) - >>= fun sidebar -> - document_of_odocl ~syntax file >>= fun doc -> - render_document renderer ~output ~sidebar ~extra_suffix ~extra doc; + Odoc_file.load_index x >>= fun index -> + let sidebar = Odoc_document.Sidebar.of_lang index.sidebar in + Ok (Some sidebar, Some index)) + >>= fun (sidebar, index) -> + let breadcrumbs = Odoc_document.Breadcrumbs.of_lang ~index id in + render_document renderer ~output ~sidebar ~breadcrumbs ~extra_suffix ~extra + doc; Ok () let documents_of_implementation ~warnings_options:_ ~syntax impl source_file = @@ -111,8 +123,15 @@ let generate_source_odoc ~syntax ~warnings_options ~renderer ~output | Odoc_file.Impl_content impl -> documents_of_implementation ~warnings_options ~syntax impl source_file >>= fun docs -> + let breadcrumbs = + match impl.id with + | Some id -> + Odoc_document.Breadcrumbs.of_lang ~index:None (id :> Id.OdocId.t) + | None -> Odoc_document.Breadcrumbs.empty + in List.iter - (render_document renderer ~output ~sidebar:None ~extra_suffix ~extra) + (render_document renderer ~output ~sidebar:None ~breadcrumbs + ~extra_suffix ~extra) docs; Ok () | Page_content _ | Unit_content _ | Asset_content _ -> @@ -137,8 +156,9 @@ let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir document_of_input ~resolver ~warnings_options ~syntax odoctree else document_of_odocl ~syntax odoctree in - doc >>= fun doc -> - let pages = renderer.Renderer.render extra None doc in + doc >>= fun (_id, doc) -> + let breadcrumbs = Breadcrumbs.empty in + let pages = renderer.Renderer.render extra ~sidebar:None ~breadcrumbs 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); @@ -153,7 +173,10 @@ let targets_source_odoc ~syntax ~warnings_options ~renderer ~output:root_dir >>= fun docs -> List.iter (fun doc -> - let pages = renderer.Renderer.render extra None doc in + let breadcrumbs = Breadcrumbs.empty in + let pages = + renderer.Renderer.render extra ~sidebar:None ~breadcrumbs doc + in Renderer.traverse pages ~f:(fun filename _content -> let filename = Fpath.normalize @@ Fs.File.append root_dir filename diff --git a/src/odoc/resolver.ml b/src/odoc/resolver.ml index ad780a1100..b7c9f3a6f7 100644 --- a/src/odoc/resolver.ml +++ b/src/odoc/resolver.ml @@ -499,11 +499,11 @@ let all_pages ?root ({ pages; _ } : t) = let filter (root : Odoc_model.Root.t) = match root with | { - file = Page { title; _ }; + file = Page info; id = { iv = #Odoc_model.Paths.Identifier.Page.t_pv; _ } as id; _; } -> - Some (id, title) + Some (id, info) | _ -> None in match pages with diff --git a/src/odoc/resolver.mli b/src/odoc/resolver.mli index 0cc5472829..15d63abc71 100644 --- a/src/odoc/resolver.mli +++ b/src/odoc/resolver.mli @@ -47,8 +47,7 @@ val lookup_page : t -> string -> Odoc_model.Lang.Page.t option val all_pages : ?root:string -> t -> - (Odoc_model.Paths.Identifier.Page.t * Odoc_model.Comment.link_content option) - list + (Odoc_model.Paths.Identifier.Page.t * Odoc_model.Root.Odoc_file.page) list val all_units : library:string -> t -> Odoc_model.Paths.Identifier.RootModule.t list diff --git a/test/integration/html_support_files.t/run.t b/test/integration/html_support_files.t/run.t index 4bfa5b8b4c..a010ca0bef 100644 --- a/test/integration/html_support_files.t/run.t +++ b/test/integration/html_support_files.t/run.t @@ -1,6 +1,9 @@ $ odoc support-files -o with-theme $ find with-theme | sort with-theme + with-theme/.formatted + with-theme/.formatted/dune + with-theme/dune with-theme/fonts with-theme/fonts/KaTeX_AMS-Regular.woff2 with-theme/fonts/KaTeX_Caligraphic-Bold.woff2 @@ -42,6 +45,9 @@ $ odoc support-files --without-theme -o without-theme $ find without-theme | sort without-theme + without-theme/.formatted + without-theme/.formatted/dune + without-theme/dune without-theme/fonts without-theme/fonts/KaTeX_AMS-Regular.woff2 without-theme/fonts/KaTeX_Caligraphic-Bold.woff2 diff --git a/test/integration/json_expansion_with_sources.t/run.t b/test/integration/json_expansion_with_sources.t/run.t index 4481715140..4f88d1a168 100644 --- a/test/integration/json_expansion_with_sources.t/run.t +++ b/test/integration/json_expansion_with_sources.t/run.t @@ -47,4 +47,4 @@ Test the JSON output in the presence of expanded modules. {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../../index.html","kind":"module"},{"name":"A","href":"../index.html","kind":"module"},{"name":"B","href":"#","kind":"module"}],"toc":[],"global_toc":null,"source_anchor":"../../../src/a.ml.html#module-B","preamble":"","content":""} $ cat html/src/a.ml.html.json - {"type":"source","breadcrumbs":[{"name":"src","href":"index.html","kind":"page"},{"name":"a.ml","href":"#","kind":"source"}],"content":"
"} + {"type":"source","breadcrumbs":[{"name":"src","href":"index.html","kind":"page"},{"name":"Source a.ml","href":"#","kind":"source"}],"content":"1\u000Amodule B = struct end\u000A
"} diff --git a/test/integration/link_opts.t/run.t b/test/integration/link_opts.t/run.t index fc49054607..34dd16ef09 100644 --- a/test/integration/link_opts.t/run.t +++ b/test/integration/link_opts.t/run.t @@ -17,12 +17,10 @@ Current library is not passed: [1] $ odoc link -P pkg:h/pkg/doc -L otherlib:h/otherpkg h/pkg/doc/page-page.odoc -Current package is not passed: +Current package is not passed, this is allowed: $ odoc link -P otherpkg:h/otherpkg/doc -L libname:h/pkg/lib/libname h/pkg/lib/libname/test.odoc $ odoc link -P otherpkg:h/otherpkg/doc -L libname:h/pkg/lib/libname h/pkg/doc/page-page.odoc - ERROR: The output file must be part of a directory passed as -P - [1] Specified current package is wrong: diff --git a/test/pages/resolution.t/run.t b/test/pages/resolution.t/run.t index d0a6539edf..1816de900e 100644 --- a/test/pages/resolution.t/run.t +++ b/test/pages/resolution.t/run.t @@ -97,6 +97,8 @@ Let's also check the hierarchy of files produced: $ odoc support-files -o html $ find html -type f | sort + html/.formatted/dune + html/dune html/fonts/KaTeX_AMS-Regular.woff2 html/fonts/KaTeX_Caligraphic-Bold.woff2 html/fonts/KaTeX_Caligraphic-Regular.woff2 diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/doc/index.mld b/test/parent_id/breadcrumbs_short_title.t/pkg/doc/index.mld new file mode 100644 index 0000000000..895e102151 --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/doc/index.mld @@ -0,0 +1,5 @@ +{0 Doc index page} + +{@meta[ +short_title: Short title doc +]} diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/doc/subdir/foo.mld b/test/parent_id/breadcrumbs_short_title.t/pkg/doc/subdir/foo.mld new file mode 100644 index 0000000000..5078dcc340 --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/doc/subdir/foo.mld @@ -0,0 +1,5 @@ +{0 subdir/foo} + +{@meta[ +short_title: Short title foo +]} diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/doc/subdir/index.mld b/test/parent_id/breadcrumbs_short_title.t/pkg/doc/subdir/index.mld new file mode 100644 index 0000000000..1f46a4ee5f --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/doc/subdir/index.mld @@ -0,0 +1,5 @@ +{0 doc/subdir index page} + +{@meta[ +short_title: Short title subdir +]} diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/index.mld b/test/parent_id/breadcrumbs_short_title.t/pkg/index.mld new file mode 100644 index 0000000000..291943c6e0 --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/index.mld @@ -0,0 +1,5 @@ +{0 Package 'pkg' index page} + +{@meta[ +short_title: Short title 'pkg' +]} diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/lib/index.mld b/test/parent_id/breadcrumbs_short_title.t/pkg/lib/index.mld new file mode 100644 index 0000000000..1da65b90f6 --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/lib/index.mld @@ -0,0 +1,5 @@ +{0 Library list} + +{@meta[ +short_title: Short title library list +]} diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/lib/lname/index.mld b/test/parent_id/breadcrumbs_short_title.t/pkg/lib/lname/index.mld new file mode 100644 index 0000000000..1ecf327758 --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/lib/lname/index.mld @@ -0,0 +1,5 @@ +{0 Library index page} + +{@meta[ +short_title: Short title lname +]} diff --git a/test/parent_id/breadcrumbs_short_title.t/pkg/lib/lname/lname.mli b/test/parent_id/breadcrumbs_short_title.t/pkg/lib/lname/lname.mli new file mode 100644 index 0000000000..48451390c0 --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/pkg/lib/lname/lname.mli @@ -0,0 +1 @@ +val x : int diff --git a/test/parent_id/breadcrumbs_short_title.t/run.t b/test/parent_id/breadcrumbs_short_title.t/run.t new file mode 100644 index 0000000000..e7a0f9899f --- /dev/null +++ b/test/parent_id/breadcrumbs_short_title.t/run.t @@ -0,0 +1,70 @@ +Index pages in a directory might specify a 'short_title' that must appear in the breadcrumbs. +This applies to package and library index pages. + + $ LINK_OPTS="-P pkg:_odoc/pkg/doc -L lname:_odoc/pkg/lib/lname" + +It's not possible to link a page that is not part of a package's doc hierarchy. +This restriction should be lifted in the future. + +$ LINK_OPTS="$LINK_OPTS -P root_of_pkg:_odoc/pkg" + + $ ocamlc -c -bin-annot pkg/lib/lname/lname.mli + + $ alias compile="odoc compile --output-dir _odoc/ --parent-id" + $ compile pkg pkg/index.mld + $ compile pkg/lib pkg/lib/index.mld + $ compile pkg/lib/lname pkg/lib/lname/index.mld + $ compile pkg/lib/lname pkg/lib/lname/lname.cmti + $ compile pkg/doc pkg/doc/index.mld + $ compile pkg/doc/subdir pkg/doc/subdir/index.mld + $ compile pkg/doc/subdir pkg/doc/subdir/foo.mld + + $ find _odoc -name '*.odoc' -exec odoc link $LINK_OPTS {} ';' + $ odoc compile-index $LINK_OPTS -o _odoc/pkg/package-index.odoc-index + $ find _odoc -name '*.odocl' -exec odoc html-generate --indent --index _odoc/pkg/package-index.odoc-index -o html {} ';' + + $ nav() { sed -n '\#1\u000Amodule B = struct end\u000A