From ec61dc8c0a55b93fc4b987be2dc94e7803ab11c1 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 14:01:52 +0200 Subject: [PATCH 1/5] Remove Url.Path.pp_kind This function is a bad alias to `string_of_kind` and gets in the way of grepping. --- src/document/url.ml | 29 +++++++++++++++++------------ src/document/url.mli | 4 ---- src/html/link.ml | 2 +- src/latex/generator.ml | 7 +++---- src/manpage/link.ml | 3 ++- 5 files changed, 23 insertions(+), 22 deletions(-) diff --git a/src/document/url.ml b/src/document/url.ml index 5fbb47463c..6c33737ed5 100644 --- a/src/document/url.ml +++ b/src/document/url.ml @@ -119,8 +119,6 @@ module Path = struct | `File -> "file" | `SourcePage -> "source" - let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind) - type t = { kind : kind; parent : t option; name : string } let mk ?parent kind name = { kind; parent; name } @@ -252,8 +250,6 @@ module Anchor = struct | `Field -> "field" | `SourceAnchor -> "source-anchor" - let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind) - type t = { page : Path.t; anchor : string; kind : kind } let anchorify_path { Path.parent; name; kind } = @@ -308,7 +304,7 @@ module Anchor = struct { page; anchor = - Format.asprintf "%a-%s" pp_kind kind + Format.asprintf "%s-%s" (string_of_kind kind) (TypeName.to_string type_name); kind; } @@ -321,7 +317,7 @@ module Anchor = struct { page; anchor = - Format.asprintf "%a-%s" pp_kind kind + Format.asprintf "%s-%s" (string_of_kind kind) (ExtensionName.to_string name); kind; } @@ -332,7 +328,7 @@ module Anchor = struct { page; anchor = - Format.asprintf "%a-%s" pp_kind kind + Format.asprintf "%s-%s" (string_of_kind kind) (ExtensionName.to_string name); kind; } @@ -343,7 +339,7 @@ module Anchor = struct { page; anchor = - Format.asprintf "%a-%s" pp_kind kind + Format.asprintf "%s-%s" (string_of_kind kind) (ExceptionName.to_string name); kind; } @@ -356,7 +352,8 @@ module Anchor = struct { page; anchor = - Format.asprintf "%a-%s" pp_kind kind (ValueName.to_string name); + Format.asprintf "%s-%s" (string_of_kind kind) + (ValueName.to_string name); kind; } | { iv = `Method (parent, name); _ } -> @@ -364,13 +361,21 @@ module Anchor = struct let page = Path.from_identifier (parent :> Path.any) in let kind = `Method in Ok - { page; anchor = Format.asprintf "%a-%s" pp_kind kind str_name; kind } + { + page; + anchor = Format.asprintf "%s-%s" (string_of_kind kind) str_name; + kind; + } | { iv = `InstanceVariable (parent, name); _ } -> let str_name = InstanceVariableName.to_string name in let page = Path.from_identifier (parent :> Path.any) in let kind = `Val in Ok - { page; anchor = Format.asprintf "%a-%s" pp_kind kind str_name; kind } + { + page; + anchor = Format.asprintf "%s-%s" (string_of_kind kind) str_name; + kind; + } | { iv = `Constructor (parent, name); _ } -> from_identifier (parent :> Identifier.t) >>= fun page -> let kind = `Constructor in @@ -436,7 +441,7 @@ module Anchor = struct let page = Path.from_identifier (decl.parent :> Path.any) in let kind = `ExtensionDecl in let first_cons = Identifier.name (List.hd decl.constructors).id in - let anchor = Format.asprintf "%a-%s" pp_kind kind first_cons in + let anchor = Format.asprintf "%s-%s" (string_of_kind kind) first_cons in { page; kind; anchor } let source_anchor path anchor = { page = path; anchor; kind = `SourceAnchor } diff --git a/src/document/url.mli b/src/document/url.mli index a6c0863a6f..220b122286 100644 --- a/src/document/url.mli +++ b/src/document/url.mli @@ -23,8 +23,6 @@ module Path : sig | `File | `SourcePage ] - val pp_kind : Format.formatter -> kind -> unit - val string_of_kind : kind -> string type t = { kind : kind; parent : t option; name : string } @@ -73,8 +71,6 @@ module Anchor : sig | `Field | `SourceAnchor ] - val pp_kind : Format.formatter -> kind -> unit - val string_of_kind : kind -> string type t = { diff --git a/src/html/link.ml b/src/html/link.ml index 74c68d924c..6c45432ba7 100644 --- a/src/html/link.ml +++ b/src/html/link.ml @@ -9,7 +9,7 @@ module Path = struct let segment_to_string (kind, name) = match kind with | `Module | `Page | `File | `SourcePage -> name - | _ -> Format.asprintf "%a-%s" Url.Path.pp_kind kind name + | _ -> Format.asprintf "%s-%s" (Url.Path.string_of_kind kind) name let is_leaf_page url = url.Url.Path.kind = `LeafPage diff --git a/src/latex/generator.ml b/src/latex/generator.ml index b4cd596b10..4725c28a08 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -4,11 +4,10 @@ module Doctree = Odoc_document.Doctree module Link = struct let rec flatten_path ppf (x : Odoc_document.Url.Path.t) = + let kind = Odoc_document.Url.Path.string_of_kind x.kind in match x.parent with - | Some p -> - Fmt.pf ppf "%a-%a-%s" flatten_path p Odoc_document.Url.Path.pp_kind - x.kind x.name - | None -> Fmt.pf ppf "%a-%s" Odoc_document.Url.Path.pp_kind x.kind x.name + | Some p -> Fmt.pf ppf "%a-%s-%s" flatten_path p kind x.name + | None -> Fmt.pf ppf "%s-%s" kind x.name let page p = Format.asprintf "%a" flatten_path p diff --git a/src/manpage/link.ml b/src/manpage/link.ml index f007aa5510..16de34bd13 100644 --- a/src/manpage/link.ml +++ b/src/manpage/link.ml @@ -5,7 +5,8 @@ let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = match kind with | `Module | `Page | `LeafPage | `Class -> name - | _ -> Format.asprintf "%a-%s" Odoc_document.Url.Path.pp_kind kind name + | _ -> + Format.asprintf "%s-%s" (Odoc_document.Url.Path.string_of_kind kind) name let as_filename ?(add_ext = true) (url : Url.Path.t) = let components = Url.Path.to_list url in From 78f489ee097f53bf4b2d3b2f5b147ed8d1ce06e1 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 14:27:35 +0200 Subject: [PATCH 2/5] Make Url.Path.split more maintainable The `is_dir` function has only two purposes and is hard to maintain in the several places where it's defined. For example, when the identifier type changes. Use a pair of booleans and move its definition into the Url module instead. --- src/document/url.ml | 11 ++++++----- src/document/url.mli | 18 ++++++++---------- src/html/link.ml | 7 ++----- src/latex/generator.ml | 3 +-- src/manpage/link.ml | 6 +----- 5 files changed, 18 insertions(+), 27 deletions(-) diff --git a/src/document/url.ml b/src/document/url.ml index 6c33737ed5..acb6bb798b 100644 --- a/src/document/url.ml +++ b/src/document/url.ml @@ -208,11 +208,12 @@ module Path = struct in inner None l - let split : - is_dir:(kind -> [ `Always | `Never | `IfNotLast ]) -> - (kind * string) list -> - (kind * string) list * (kind * string) list = - fun ~is_dir l -> + let split ~is_flat ~allow_empty l = + let is_dir = + if is_flat then function + | `Page -> if allow_empty then `Always else `IfNotLast | _ -> `Never + else function `LeafPage | `File | `SourcePage -> `Never | _ -> `Always + in let rec inner dirs = function | [ ((kind, _) as x) ] when is_dir kind = `IfNotLast -> (List.rev dirs, [ x ]) diff --git a/src/document/url.mli b/src/document/url.mli index 220b122286..52ce094494 100644 --- a/src/document/url.mli +++ b/src/document/url.mli @@ -43,18 +43,16 @@ module Path : sig val of_list : (kind * string) list -> t option val split : - is_dir:(kind -> [ `Always | `Never | `IfNotLast ]) -> + is_flat:bool -> + allow_empty:bool -> (kind * string) list -> (kind * string) list * (kind * string) list - (** [split is_dir path] splits the list [path] into a directory - and filename, based on the [is_dir] function. The function - [is_dir] should return whether or not the path element [kind] - should be a directory or not. If the function [is_dir] returns - [`IfNotLast] then the element will be a directory only if it - is not the last element in the path. The return value is a tuple - of directory-type elements and filename-type elements. If the - [is_dir] function can return [`Always], the caller must be prepared - to handle the case where the filename part is empty. *) + (** [split ~is_flat path] splits the list [path] into a directory + and filename. Returns a tuple + of directory-type elements and filename-type elements. If [allow_empty] + is [true], the filename part will be empty if all components are + directory-type. If [allow_empty] is [false], the last element will part + of the filename, even if it is a directory-type. *) end module Anchor : sig diff --git a/src/html/link.ml b/src/html/link.ml index 6c45432ba7..40525ec53c 100644 --- a/src/html/link.ml +++ b/src/html/link.ml @@ -29,11 +29,8 @@ module Path = struct let get_dir_and_file ~config url = let l = Url.Path.to_list url in - let is_dir = - if Config.flat config then function `Page -> `Always | _ -> `Never - else function `LeafPage | `File | `SourcePage -> `Never | _ -> `Always - in - let dir, file = Url.Path.split ~is_dir l in + let is_flat = Config.flat config in + let dir, file = Url.Path.split ~is_flat ~allow_empty:true l in let dir = List.map segment_to_string dir in let file = match file with diff --git a/src/latex/generator.ml b/src/latex/generator.ml index 4725c28a08..3494fb4f37 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -33,8 +33,7 @@ module Link = struct let get_dir_and_file url = let open Odoc_document in let l = Url.Path.to_list url in - let is_dir = function `Page -> `IfNotLast | _ -> `Never in - let dir, file = Url.Path.split ~is_dir l in + let dir, file = Url.Path.split ~is_flat:true ~allow_empty:false l in let segment_to_string (_kind, name) = name in ( List.map segment_to_string dir, String.concat "." (List.map segment_to_string file) ) diff --git a/src/manpage/link.ml b/src/manpage/link.ml index 16de34bd13..862a4be153 100644 --- a/src/manpage/link.ml +++ b/src/manpage/link.ml @@ -10,11 +10,7 @@ let segment_to_string (kind, name) = let as_filename ?(add_ext = true) (url : Url.Path.t) = let components = Url.Path.to_list url in - let dir, path = - Url.Path.split - ~is_dir:(function `Page -> `IfNotLast | _ -> `Never) - components - in + let dir, path = Url.Path.split ~is_flat:true ~allow_empty:false components in let dir = List.map segment_to_string dir in let path = String.concat "." (List.map segment_to_string path) in let str_path = String.concat Fpath.dir_sep (dir @ [ path ]) in From bcda666e8b1bfbdb538f54aeb8e701816e8d4d6c Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 13:45:17 +0200 Subject: [PATCH 3/5] Identify libraries in identifiers The new constructor identify which part of the identifier is not just a page but a library. This will be used to propagate the information to breadcrumbs. --- src/document/doctree.ml | 3 +- src/document/url.ml | 17 +++++++- src/document/url.mli | 3 +- src/html/link.ml | 2 +- src/latex/generator.ml | 2 +- src/loader/implementation.ml | 2 +- src/manpage/link.ml | 4 +- src/model/paths.ml | 16 +++++--- src/model/paths_types.ml | 13 +++++- src/model/root.ml | 7 +++- src/model_desc/paths_desc.ml | 5 +++ src/occurrences/table.ml | 4 +- src/odoc/bin/main.ml | 5 +-- src/odoc/compile.ml | 14 ++++++- src/search/json_index/json_search.ml | 1 + src/utils/odoc_utils.ml | 1 + src/xref2/component.ml | 2 +- src/xref2/shape_tools.cppo.ml | 2 +- test/integration/html_opts.t/run.t | 2 +- test/pages/resolution.t/run.t | 3 +- test/xref2/canonical_module.t/run.t | 12 +++--- test/xref2/canonical_module_type.t/run.t | 8 ++-- test/xref2/canonical_type.t/run.t | 6 ++- test/xref2/cross_references.t/run.t | 6 ++- test/xref2/gh749.t/run.t | 10 ++--- test/xref2/github_issue_917.t/run.t | 8 ++-- test/xref2/labels/ambiguous_label.t/run.t | 16 ++++---- test/xref2/labels/labels.t/run.t | 30 +++++++------- .../labels/shadowed_in_submodules.t/run.t | 6 +-- test/xref2/map_ref_to_url.t/run.t | 2 +- test/xref2/module_list.t/run.t | 40 +++++++++---------- test/xref2/path_references.t/run.t | 10 ++--- test/xref2/references_scope.t/run.t | 26 ++++++------ test/xref2/references_to_pages.t/run.t | 4 +- test/xref2/strengthen_includes.t/run.t | 1 - test/xref2/with.t/run.t | 3 +- 36 files changed, 175 insertions(+), 121 deletions(-) diff --git a/src/document/doctree.ml b/src/document/doctree.ml index cfdd2cfa4f..df18e4ad91 100644 --- a/src/document/doctree.ml +++ b/src/document/doctree.ml @@ -329,11 +329,12 @@ end = struct | `ClassType -> prefix "Class type" | `Class -> prefix "Class" | `SourcePage -> prefix "Source file" + | `Library -> prefix "Library" | `Page | `LeafPage | `File -> [] let make_name_from_path { Url.Path.name; parent; _ } = match parent with - | None | Some { kind = `Page; _ } -> name + | None | Some { kind = `Page | `Library; _ } -> name | Some p -> Printf.sprintf "%s.%s" p.name name let render_title ?source_anchor (p : Page.t) = diff --git a/src/document/url.ml b/src/document/url.ml index acb6bb798b..f643b4ede1 100644 --- a/src/document/url.ml +++ b/src/document/url.ml @@ -106,7 +106,8 @@ module Path = struct | `Class | `ClassType | `File - | `SourcePage ] + | `SourcePage + | `Library ] let string_of_kind : kind -> string = function | `Page -> "page" @@ -118,6 +119,7 @@ module Path = struct | `ClassType -> "class-type" | `File -> "file" | `SourcePage -> "source" + | `Library -> "library" type t = { kind : kind; parent : t option; name : string } @@ -144,6 +146,13 @@ module Path = struct let kind = `Page in let name = PageName.to_string page_name in mk ?parent kind name + | { iv = `Library (parent, _page_name, libname); _ } -> + let parent = + match parent with + | Some p -> Some (from_identifier (p :> any)) + | None -> None + in + mk ?parent `Library libname | { iv = `LeafPage (parent, page_name); _ } -> let parent = match parent with @@ -211,7 +220,8 @@ module Path = struct let split ~is_flat ~allow_empty l = let is_dir = if is_flat then function - | `Page -> if allow_empty then `Always else `IfNotLast | _ -> `Never + | `Page | `Library -> if allow_empty then `Always else `IfNotLast + | _ -> `Never else function `LeafPage | `File | `SourcePage -> `Never | _ -> `Always in let rec inner dirs = function @@ -289,6 +299,9 @@ module Anchor = struct | { iv = `Page _; _ } as p -> let page = Path.from_identifier (p :> Path.any) in Ok { page; kind = `Page; anchor = "" } + | { iv = `Library _; _ } as p -> + let page = Path.from_identifier (p :> Path.any) in + Ok { page; kind = `Library; anchor = "" } | { iv = `LeafPage _; _ } as p -> let page = Path.from_identifier (p :> Path.any) in Ok { page; kind = `LeafPage; anchor = "" } diff --git a/src/document/url.mli b/src/document/url.mli index 52ce094494..4fae42ca7c 100644 --- a/src/document/url.mli +++ b/src/document/url.mli @@ -21,7 +21,8 @@ module Path : sig | `Class | `ClassType | `File - | `SourcePage ] + | `SourcePage + | `Library ] val string_of_kind : kind -> string diff --git a/src/html/link.ml b/src/html/link.ml index 40525ec53c..6573525f30 100644 --- a/src/html/link.ml +++ b/src/html/link.ml @@ -8,7 +8,7 @@ module Path = struct let segment_to_string (kind, name) = match kind with - | `Module | `Page | `File | `SourcePage -> name + | `Module | `Page | `File | `Library | `SourcePage -> name | _ -> Format.asprintf "%s-%s" (Url.Path.string_of_kind kind) name let is_leaf_page url = url.Url.Path.kind = `LeafPage diff --git a/src/latex/generator.ml b/src/latex/generator.ml index 3494fb4f37..93fae10399 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -18,7 +18,7 @@ module Link = struct let rec is_class_or_module_path (url : Odoc_document.Url.Path.t) = match url.kind with - | `Module | `LeafPage | `Class | `Page -> ( + | `Module | `LeafPage | `Class | `Page | `Library -> ( match url.parent with | None -> true | Some url -> is_class_or_module_path url) diff --git a/src/loader/implementation.ml b/src/loader/implementation.ml index 580888bf08..9b0ff00048 100644 --- a/src/loader/implementation.ml +++ b/src/loader/implementation.ml @@ -221,7 +221,7 @@ let anchor_of_identifier id = | `Class (parent, name) -> let anchor = anchor `Class (TypeName.to_string name) in continue anchor parent - | `Page _ -> assert false + | `Page _ | `Library _ -> assert false | `LeafPage _ -> assert false | `CoreType _ -> assert false | `SourceLocation _ -> assert false diff --git a/src/manpage/link.ml b/src/manpage/link.ml index 862a4be153..eb97598ced 100644 --- a/src/manpage/link.ml +++ b/src/manpage/link.ml @@ -4,7 +4,7 @@ let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = match kind with - | `Module | `Page | `LeafPage | `Class -> name + | `Module | `Page | `Library | `LeafPage | `Class -> name | _ -> Format.asprintf "%s-%s" (Odoc_document.Url.Path.string_of_kind kind) name @@ -18,7 +18,7 @@ let as_filename ?(add_ext = true) (url : Url.Path.t) = let rec is_class_or_module_path (url : Url.Path.t) = match url.kind with - | `Module | `LeafPage | `Page | `Class -> ( + | `Module | `LeafPage | `Page | `Library | `Class -> ( match url.parent with | None -> true | Some url -> is_class_or_module_path url) diff --git a/src/model/paths.ml b/src/model/paths.ml index e055b0202e..7f7da1f44b 100644 --- a/src/model/paths.ml +++ b/src/model/paths.ml @@ -14,6 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_utils module Ocaml_ident = Ident module Ocaml_env = Env @@ -32,7 +33,7 @@ module Identifier = struct fun x -> match x.iv with | `Root (_, name) -> ModuleName.to_string name - | `Page (_, name) -> PageName.to_string name + | `Library (_, name, _) | `Page (_, name) -> PageName.to_string name | `LeafPage (_, name) -> PageName.to_string name | `Module (_, name) -> ModuleName.to_string name | `Parameter (_, name) -> ModuleName.to_string name @@ -64,7 +65,7 @@ module Identifier = struct fun x -> match x.iv with | `Root (_, name) -> ModuleName.is_hidden name - | `Page (_, _) -> false + | `Page (_, _) | `Library _ -> false | `LeafPage (_, _) -> false | `Module (_, name) -> ModuleName.is_hidden name | `Parameter (_, name) -> ModuleName.is_hidden name @@ -94,9 +95,13 @@ module Identifier = struct fun x -> match x.iv with | `Root (_, name) -> [ ModuleName.to_string name ] - | `Page (None, name) -> [ PageName.to_string name ] - | `Page (Some parent, name) -> - PageName.to_string name :: full_name_aux (parent :> t) + | `Page (parent, name) | `Library (parent, name, _) -> + let parent = + match parent with + | Some parent -> full_name_aux (parent :> t) + | None -> [] + in + PageName.to_string name :: parent | `LeafPage (None, name) -> [ PageName.to_string name ] | `LeafPage (Some parent, name) -> PageName.to_string name :: full_name_aux (parent :> t) @@ -156,6 +161,7 @@ module Identifier = struct | { iv = `Root _; _ } as p -> (p :> label_parent) | { iv = `Page _; _ } as p -> (p :> label_parent) | { iv = `LeafPage _; _ } as p -> (p :> label_parent) + | { iv = `Library _; _ } as p -> (p :> label_parent) | { iv = `Module (p, _); _ } | { iv = `ModuleType (p, _); _ } | { iv = `Parameter (p, _); _ } diff --git a/src/model/paths_types.ml b/src/model/paths_types.ml index 77cad0bdca..4b76789ee9 100644 --- a/src/model/paths_types.ml +++ b/src/model/paths_types.ml @@ -5,7 +5,12 @@ type 'a id = { iv : 'a; ihash : int; ikey : string } (** @canonical Odoc_model.Paths.Identifier.id *) module Identifier = struct - type container_page_pv = [ `Page of container_page option * PageName.t ] + type container_page_pv = + [ `Page of container_page option * PageName.t + | `Library of + container_page option + * PageName.t + * string (* (parent, dirname, libname) *) ] (** @canonical Odoc_model.Paths.Identifier.ContainerPage.t_pv *) and container_page = container_page_pv id @@ -232,7 +237,11 @@ module Identifier = struct (** @canonical Odoc_model.Paths.Identifier.NonSrc.t *) type any_pv = - [ non_src_pv | source_page_pv | source_location_pv | asset_file_pv ] + [ non_src_pv + | source_page_pv + | source_location_pv + | asset_file_pv + | container_page_pv ] (** @canonical Odoc_model.Paths.Identifier.t_pv *) and any = any_pv id diff --git a/src/model/root.ml b/src/model/root.ml index 055d045234..f84180a6be 100644 --- a/src/model/root.ml +++ b/src/model/root.ml @@ -78,10 +78,13 @@ let to_string t = let rec loop_pp fmt parent = match parent.Paths.Identifier.iv with | `SourceDir (p, name) -> Format.fprintf fmt "%a::%s" loop_pp p name - | `Page _ as iv -> Format.fprintf fmt "%a" pp { parent with iv } + | (`Page _ | `Library _) as iv -> + Format.fprintf fmt "%a" pp { parent with iv } in Format.fprintf fmt "%a::%s" loop_pp parent name - | `LeafPage (parent, name) | `Page (parent, name) -> ( + | `LeafPage (parent, name) + | `Page (parent, name) + | `Library (parent, name, _) -> ( match parent with | Some p -> Format.fprintf fmt "%a::%a" pp diff --git a/src/model_desc/paths_desc.ml b/src/model_desc/paths_desc.ml index 2efe8c6e7c..b6e20f58e2 100644 --- a/src/model_desc/paths_desc.ml +++ b/src/model_desc/paths_desc.ml @@ -73,6 +73,11 @@ module General_paths = struct ( "`Page", ((parent :> id_t option), name), Pair (Option identifier, Names.pagename) ) + | `Library (parent, name, libname) -> + C + ( "`Library", + ((parent :> id_t option), name, libname), + Triple (Option identifier, Names.pagename, string) ) | `LeafPage (parent, name) -> C ( "`LeafPage", diff --git a/src/occurrences/table.ml b/src/occurrences/table.ml index b6f233c3e7..bb26dfd750 100644 --- a/src/occurrences/table.ml +++ b/src/occurrences/table.ml @@ -50,7 +50,7 @@ let add ?(quantity = 1) tbl id = | `Root _ -> incr tbl id | `SourcePage _ | `Page _ | `LeafPage _ | `SourceLocation _ | `CoreException _ | `Label _ | `SourceLocationMod _ | `Result _ - | `AssetFile _ | `SourceLocationInternal _ -> + | `AssetFile _ | `SourceLocationInternal _ | `Library _ -> assert false in let _htbl = add ~kind:`Direct id in @@ -80,7 +80,7 @@ let rec get t id = | `Root _ -> ( try Some (H.find t id) with Not_found -> None) | `SourcePage _ | `Page _ | `LeafPage _ | `CoreType _ | `SourceLocation _ | `CoreException _ | `Label _ | `SourceLocationMod _ | `Result _ - | `AssetFile _ | `SourceLocationInternal _ -> + | `AssetFile _ | `SourceLocationInternal _ | `Library _ -> None let get t id = diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index e9936c3271..4fc1b925c4 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1339,9 +1339,8 @@ module Depends = struct module Link = struct let rec fmt_page pp page = match page.Odoc_model.Paths.Identifier.iv with - | `Page (parent_opt, name) -> - Format.fprintf pp "%a%a" fmt_parent_opt parent_opt - Odoc_model.Names.PageName.fmt name + | `Page (parent_opt, name) + | `Library (parent_opt, name, _) | `LeafPage (parent_opt, name) -> Format.fprintf pp "%a%a" fmt_parent_opt parent_opt Odoc_model.Names.PageName.fmt name diff --git a/src/odoc/compile.ml b/src/odoc/compile.ml index 92cf62bc85..641f324267 100644 --- a/src/odoc/compile.ml +++ b/src/odoc/compile.ml @@ -46,7 +46,7 @@ let rec path_of_id output_dir id = | None -> Fpath.v output_dir | Some id -> ( match (id : Paths.Identifier.ContainerPage.t).iv with - | `Page (parent, p) -> + | `Page (parent, p) | `Library (parent, p, _) -> let d = path_of_id output_dir parent in Fpath.(d / PageName.to_string p)) @@ -88,7 +88,8 @@ let resolve_parent_page resolver f = | Module_child _ -> Error (`Msg "Expecting page as parent") in let extract_parent = function - | { Paths.Identifier.iv = `Page _; _ } as container -> Ok container + | { Paths.Identifier.iv = `Page _ | `Library _; _ } as container -> + Ok container | { Paths.Identifier.iv = `LeafPage _; _ } -> Error (`Msg "Specified parent is not a parent of this file") in @@ -319,12 +320,21 @@ let compile ~resolver ~hidden ~cli_spec ~warnings_options input = >>= fun { parent_id; output; parents_children; children } -> let ext = Fs.File.get_ext input in if ext = ".mld" then + (* TODO: A page might be in a library, for example the library entry page. *) mld ~parent_id ~parents_children ~output ~warnings_options ~children input else check_is_empty "Not expecting children (--child) when compiling modules." children >>= fun () -> handle_file_ext ext >>= fun input_type -> + let parent_id = + match parent_id with + | Some ({ iv = `Page (pparent, pname); _ } as id) -> + (* TODO: This should match the library name passed to the link command. *) + Some + { id with iv = `Library (pparent, pname, PageName.to_string pname) } + | pid -> pid + in let make_root = root_of_compilation_unit ~parent_id ~parents_children ~hidden ~output in diff --git a/src/search/json_index/json_search.ml b/src/search/json_index/json_search.ml index 0301e4039e..1324a0aba4 100644 --- a/src/search/json_index/json_search.ml +++ b/src/search/json_index/json_search.ml @@ -39,6 +39,7 @@ let rec of_id x = match x.iv with | `Root (_, name) -> [ ret "Root" (ModuleName.to_string name) ] | `Page (_, name) -> [ ret "Page" (PageName.to_string name) ] + | `Library (_, name, _) -> [ ret "Library" (PageName.to_string name) ] | `AssetFile (_, name) -> [ ret "Asset" (AssetName.to_string name) ] | `LeafPage (_, name) -> [ ret "Page" (PageName.to_string name) ] | `Module (parent, name) -> diff --git a/src/utils/odoc_utils.ml b/src/utils/odoc_utils.ml index d3654cab29..2777b4f051 100644 --- a/src/utils/odoc_utils.ml +++ b/src/utils/odoc_utils.ml @@ -79,6 +79,7 @@ end module Option = struct let map f = function None -> None | Some x -> Some (f x) + let to_list = function None -> [] | Some x -> [ x ] end module Fun = struct diff --git a/src/xref2/component.ml b/src/xref2/component.ml index d3eb1e2bca..07ad39e483 100644 --- a/src/xref2/component.ml +++ b/src/xref2/component.ml @@ -712,7 +712,7 @@ module Fmt = struct Format.fprintf ppf "%a.%s" (model_identifier c) (p :> id) (ExtensionName.to_string name) - | `Page (_, name) | `LeafPage (_, name) -> + | `Page (_, name) | `Library (_, name, _) | `LeafPage (_, name) -> Format.fprintf ppf "%s" (PageName.to_string name) | `SourcePage (p, name) -> Format.fprintf ppf "%a/%s" (model_identifier c) (p :> id) name diff --git a/src/xref2/shape_tools.cppo.ml b/src/xref2/shape_tools.cppo.ml index 74b8519a08..5f7b555795 100644 --- a/src/xref2/shape_tools.cppo.ml +++ b/src/xref2/shape_tools.cppo.ml @@ -50,7 +50,7 @@ let rec shape_of_id env : proj parent Kind.Class_type (TypeName.to_string_unsafe name) | `Page _ | `LeafPage _ | `Label _ | `CoreType _ | `CoreException _ | `Constructor _ | `Field _ | `Method _ | `InstanceVariable _ | `Parameter _ - -> + | `Library _ -> (* Not represented in shapes. *) None diff --git a/test/integration/html_opts.t/run.t b/test/integration/html_opts.t/run.t index 550cedbbb3..984dd06609 100644 --- a/test/integration/html_opts.t/run.t +++ b/test/integration/html_opts.t/run.t @@ -22,7 +22,7 @@ Generate --as-json embeddable HTML fragment output: $ odoc html-generate test.odocl -o html --as-json --indent $ cat html/test/Test/index.html.json - {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"test","href":"../index.html","kind":"page"},{"name":"Test","href":"#","kind":"module"}],"toc":[{"title":"Section 1","href":"#section-1","children":[]},{"title":"Section 2","href":"#section-2","children":[]}],"global_toc":null,"source_anchor":null,"preamble":"

Test

","content":"

Section 1

\u000A
\u000A \u000A type t\u000A
\u000A

Section 2

\u000A
\u000A \u000A type u\u000A
\u000A
"} + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"test","href":"../index.html","kind":"library"},{"name":"Test","href":"#","kind":"module"}],"toc":[{"title":"Section 1","href":"#section-1","children":[]},{"title":"Section 2","href":"#section-2","children":[]}],"global_toc":null,"source_anchor":null,"preamble":"

Test

","content":"

Section 1

\u000A
\u000A \u000A type t\u000A
\u000A

Section 2

\u000A
\u000A \u000A type u\u000A
\u000A
"} $ odoc html-targets test.odocl -o html --as-json --indent html/test/Test/index.html.json diff --git a/test/pages/resolution.t/run.t b/test/pages/resolution.t/run.t index d0a6539edf..59b3cb3ca3 100644 --- a/test/pages/resolution.t/run.t +++ b/test/pages/resolution.t/run.t @@ -74,7 +74,7 @@ This is the '{!childmodule:M1}' reference "`Root": [ { "Some": { - "`Page": [ + "`Library": [ { "Some": { "`Page": [ @@ -83,6 +83,7 @@ This is the '{!childmodule:M1}' reference ] } }, + "sub1", "sub1" ] } diff --git a/test/xref2/canonical_module.t/run.t b/test/xref2/canonical_module.t/run.t index dac3d73c25..d09195ceb4 100644 --- a/test/xref2/canonical_module.t/run.t +++ b/test/xref2/canonical_module.t/run.t @@ -21,9 +21,9 @@ have it in the top-comment. Every references should be marked as canonical: $ odoc_print test.odocl | jq -c ".content.Module.items | .[] | .Module[1].type_.Alias[0] | select(.)" - {"`Resolved":{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test_x"]}},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"X"]}}}]}} - {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test_x"]}},{"`Dot":[{"`Root":"Test"},"X"]}]},"Out"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"X_out"]}}}]}} - {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test_x"]}},{"`Dot":[{"`Root":"Test"},"X"]}]},"In"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"X_in"]}}}]}} - {"`Resolved":{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test_y"]}},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"Y"]}}}]}} - {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test_y"]}},{"`Dot":[{"`Root":"Test"},"Y"]}]},"Out"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"Y_out"]}}}]}} - {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test_y"]}},{"`Dot":[{"`Root":"Test"},"Y"]}]},"In"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"Y_in"]}}}]}} + {"`Resolved":{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test_x"]}},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"X"]}}}]}} + {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test_x"]}},{"`Dot":[{"`Root":"Test"},"X"]}]},"Out"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"X_out"]}}}]}} + {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test_x"]}},{"`Dot":[{"`Root":"Test"},"X"]}]},"In"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"X_in"]}}}]}} + {"`Resolved":{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test_y"]}},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"Y"]}}}]}} + {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test_y"]}},{"`Dot":[{"`Root":"Test"},"Y"]}]},"Out"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"Y_out"]}}}]}} + {"`Resolved":{"`Canonical":[{"`Module":[{"`Canonical":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test_y"]}},{"`Dot":[{"`Root":"Test"},"Y"]}]},"In"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"Y_in"]}}}]}} diff --git a/test/xref2/canonical_module_type.t/run.t b/test/xref2/canonical_module_type.t/run.t index 609ef33b9b..24d74effa2 100644 --- a/test/xref2/canonical_module_type.t/run.t +++ b/test/xref2/canonical_module_type.t/run.t @@ -37,8 +37,8 @@ constructor where the second element of the tuple is Resolved. Every module type aliases and the path they link to: $ odoc_print test.odocl | jq -c '.content.Module.items | .[] | select(.ModuleType.expr.Some.Path) | .ModuleType | { "from": .id, "to": .expr.Some.Path.p_path }' - {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"X"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"B"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"X"]}}}]}}} - {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"Y"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"A"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"Y"]}}}]}}} - {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"Z"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"A"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"Y"]}}}]}}} - {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"AB"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"AA"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Page":["None","x"]}},"Test"]},"AB"]}}}]}}} + {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"X"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"B"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"X"]}}}]}}} + {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"Y"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"A"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"Y"]}}}]}}} + {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"Z"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"A"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"Y"]}}}]}}} + {"from":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"AB"]},"to":{"`Resolved":{"`CanonicalModuleType":[{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"AA"]}},{"`Resolved":{"`Identifier":{"`ModuleType":[{"`Root":[{"Some":{"`Library":["None","x","x"]}},"Test"]},"AB"]}}}]}}} diff --git a/test/xref2/canonical_type.t/run.t b/test/xref2/canonical_type.t/run.t index 8079e28729..17617fe090 100644 --- a/test/xref2/canonical_type.t/run.t +++ b/test/xref2/canonical_type.t/run.t @@ -93,8 +93,9 @@ Canonical paths should be as short as possible. As such, the following ought to "`Root": [ { "Some": { - "`Page": [ + "`Library": [ "None", + "x", "x" ] } @@ -129,8 +130,9 @@ And this one should be `` `Type(`Identifier,t) `` "`Root": [ { "Some": { - "`Page": [ + "`Library": [ "None", + "x", "x" ] } diff --git a/test/xref2/cross_references.t/run.t b/test/xref2/cross_references.t/run.t index c72f0ddf1e..7aa621ac8a 100644 --- a/test/xref2/cross_references.t/run.t +++ b/test/xref2/cross_references.t/run.t @@ -22,8 +22,9 @@ Check that references are resolved: "`Root": [ { "Some": { - "`Page": [ + "`Library": [ "None", + "test", "test" ] } @@ -49,8 +50,9 @@ Check that references are resolved: "`Root": [ { "Some": { - "`Page": [ + "`Library": [ "None", + "test", "test" ] } diff --git a/test/xref2/gh749.t/run.t b/test/xref2/gh749.t/run.t index 6269710271..5b3c6235d6 100644 --- a/test/xref2/gh749.t/run.t +++ b/test/xref2/gh749.t/run.t @@ -9,11 +9,11 @@ $ jq_scan_references() { jq -c '.. | .["`Reference"]? | select(.) | .[0]'; } $ odoc_print good_ref.odocl | jq_scan_references - {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_ref"]},"(^)"]}}} - {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_ref"]},"(^)"]}}} - {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_ref"]},"(^)"]}}} - {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_ref"]},"(*)"]}}} - {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_ref"]},"(*)"]}}} + {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_ref"]},"(^)"]}}} + {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_ref"]},"(^)"]}}} + {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_ref"]},"(^)"]}}} + {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_ref"]},"(*)"]}}} + {"`Resolved":{"`Identifier":{"`Value":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_ref"]},"(*)"]}}} $ odoc_print bad_ref.odocl | jq_scan_references {"`Root":["( ^ )","`TUnknown"]} diff --git a/test/xref2/github_issue_917.t/run.t b/test/xref2/github_issue_917.t/run.t index 46c60857b8..c6982ef97f 100644 --- a/test/xref2/github_issue_917.t/run.t +++ b/test/xref2/github_issue_917.t/run.t @@ -7,13 +7,13 @@ Every references in `page-foo.odocl` should resolve: $ odoc_print page-foo.odocl | jq_scan_references - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Foo"]}}} - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Foo"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Foo"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Foo"]}}} {"`Resolved":{"`Identifier":{"`LeafPage":[{"Some":{"`Page":["None","test"]}},"foo"]}}} Every references in `foo.odocl` should resolve: $ odoc_print foo.odocl | jq_scan_references - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Foo"]}}} - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Foo"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Foo"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Foo"]}}} {"`Resolved":{"`Identifier":{"`LeafPage":[{"Some":{"`Page":["None","test"]}},"foo"]}}} diff --git a/test/xref2/labels/ambiguous_label.t/run.t b/test/xref2/labels/ambiguous_label.t/run.t index ed422d4a3c..4a454bd0d6 100644 --- a/test/xref2/labels/ambiguous_label.t/run.t +++ b/test/xref2/labels/ambiguous_label.t/run.t @@ -14,12 +14,12 @@ Labels don't follow OCaml's scoping rules: Contains some ambiguous labels: $ odoc_print test.odocl | jq -c '.. | .["`Heading"]? | select(.) | .[1]' - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"section-1"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"example"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"section-2"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"example"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"example"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"example_3"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"section-1"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"example"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"section-2"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"example"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"example"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"example_3"]} $ odoc html-generate --indent -o html test.odocl @@ -44,10 +44,10 @@ References should resolve to the first occurence of the ambiguous label. It is not possible to use the internal label name in references: $ odoc_print test.odocl | jq -c '.. | .["`Reference"]? | select(.)' - [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"example"]}}},[{"`Word":"Should"},"`Space",{"`Word":"resolve"},"`Space",{"`Word":"to"},"`Space",{"`Word":"the"},"`Space",{"`Word":"first"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"example"]}}},[{"`Word":"Should"},"`Space",{"`Word":"resolve"},"`Space",{"`Word":"to"},"`Space",{"`Word":"the"},"`Space",{"`Word":"first"},"`Space",{"`Word":"label"}]] [{"`Root":["example_2","`TUnknown"]},[{"`Word":"Shouldn't"},"`Space",{"`Word":"resolve"}]] A second module has a reference to the ambiguous label: $ odoc_print test_2.odocl | jq -c '.. | .["`Reference"]? | select(.)' - [{"`Resolved":{"`Label":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]}},"example"]}},[{"`Word":"Should"},"`Space",{"`Word":"resolve"},"`Space",{"`Word":"to"},"`Space",{"`Word":"the"},"`Space",{"`Word":"first"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]}},"example"]}},[{"`Word":"Should"},"`Space",{"`Word":"resolve"},"`Space",{"`Word":"to"},"`Space",{"`Word":"the"},"`Space",{"`Word":"first"},"`Space",{"`Word":"label"}]] diff --git a/test/xref2/labels/labels.t/run.t b/test/xref2/labels/labels.t/run.t index 7006399c71..07d9eaf021 100644 --- a/test/xref2/labels/labels.t/run.t +++ b/test/xref2/labels/labels.t/run.t @@ -15,26 +15,26 @@ Labels: Some are not in order because the 'doc' field appears after the rest in the output. $ odoc_print test.odocl | jq -c '.. | .["`Heading"]? | select(.) | .[1]' - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"A"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"B"]} - {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]},"C"]} - {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]},"D"]} - {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]},"B"]} - {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"N"]},"B"]} - {"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"B"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"A"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"B"]} + {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]},"C"]} + {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]},"D"]} + {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]},"B"]} + {"`Label":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"N"]},"B"]} + {"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"B"]} References to the labels: We expect resolved references and the heading text filled in. $ odoc_print test.odocl | jq -c '.. | .["`Reference"]? | select(.)' - [{"`Resolved":{"`Identifier":{"`Label":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"N"]},"B"]}}},[{"`Word":"An"},"`Space",{"`Word":"other"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] - [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]}},"B"]}},[{"`Word":"Potentially"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] - [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"A"]}}},[{"`Word":"First"},"`Space",{"`Word":"label"}]] - [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"B"]}}},[{"`Word":"Dupplicate"},"`Space",{"`Word":"B"}]] - [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]}},"C"]}},[{"`Word":"First"},"`Space",{"`Word":"label"},"`Space",{"`Word":"of"},"`Space",{"`Word":"M"}]] - [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]}},"D"]}},[{"`Word":"Floating"},"`Space",{"`Word":"label"},"`Space",{"`Word":"in"},"`Space",{"`Word":"M"}]] - [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"M"]}},"B"]}},[{"`Word":"Potentially"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] - [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"N"]}},"B"]}},[{"`Word":"An"},"`Space",{"`Word":"other"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Identifier":{"`Label":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"N"]},"B"]}}},[{"`Word":"An"},"`Space",{"`Word":"other"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]}},"B"]}},[{"`Word":"Potentially"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"A"]}}},[{"`Word":"First"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"B"]}}},[{"`Word":"Dupplicate"},"`Space",{"`Word":"B"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]}},"C"]}},[{"`Word":"First"},"`Space",{"`Word":"label"},"`Space",{"`Word":"of"},"`Space",{"`Word":"M"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]}},"D"]}},[{"`Word":"Floating"},"`Space",{"`Word":"label"},"`Space",{"`Word":"in"},"`Space",{"`Word":"M"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"M"]}},"B"]}},[{"`Word":"Potentially"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"N"]}},"B"]}},[{"`Word":"An"},"`Space",{"`Word":"other"},"`Space",{"`Word":"conflicting"},"`Space",{"`Word":"label"}]] $ odoc html-generate --indent -o html test.odocl diff --git a/test/xref2/labels/shadowed_in_submodules.t/run.t b/test/xref2/labels/shadowed_in_submodules.t/run.t index 3050aeda71..6c86b3c208 100644 --- a/test/xref2/labels/shadowed_in_submodules.t/run.t +++ b/test/xref2/labels/shadowed_in_submodules.t/run.t @@ -7,6 +7,6 @@ There should be no ambiguous labels in this example. All the references should resolve and point to what's written in the text. $ odoc_print test.odocl | jq -c '.. | .["`Reference"]? | select(.)' - [{"`Resolved":{"`Identifier":{"`Label":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"X"]},"foo"]}}},[{"`Word":"Expecting"},"`Space",{"`Word":"H2"}]] - [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"foo"]}}},[{"`Word":"Expecting"},"`Space",{"`Word":"H1"}]] - [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Test"]},"X"]}},"foo"]}},[{"`Word":"Expecting"},"`Space",{"`Word":"H2"}]] + [{"`Resolved":{"`Identifier":{"`Label":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"X"]},"foo"]}}},[{"`Word":"Expecting"},"`Space",{"`Word":"H2"}]] + [{"`Resolved":{"`Identifier":{"`Label":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"foo"]}}},[{"`Word":"Expecting"},"`Space",{"`Word":"H1"}]] + [{"`Resolved":{"`Label":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Test"]},"X"]}},"foo"]}},[{"`Word":"Expecting"},"`Space",{"`Word":"H2"}]] diff --git a/test/xref2/map_ref_to_url.t/run.t b/test/xref2/map_ref_to_url.t/run.t index 7d415ad5d8..4f86f95e1f 100644 --- a/test/xref2/map_ref_to_url.t/run.t +++ b/test/xref2/map_ref_to_url.t/run.t @@ -13,7 +13,7 @@ The root-url argument prepends a string to the html url Generate latex url $ odoc latex-url -I . Foo.t - page-test-module-Foo-type-t + library-test-module-Foo-type-t When the reference cannot be resolved. $ odoc html-url -I . Foo.u diff --git a/test/xref2/module_list.t/run.t b/test/xref2/module_list.t/run.t index 91966549fc..4ec31ef58d 100644 --- a/test/xref2/module_list.t/run.t +++ b/test/xref2/module_list.t/run.t @@ -15,46 +15,46 @@ Everything should resolve: $ odoc_print main.odocl | jq -c '.. | .["`Modules"]? | select(.) | .[] | .[]' - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"External"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"External"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"External"},{"`Word":"."}]} - {"`Resolved":{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"External"]}},"X"]}} + {"`Resolved":{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"External"]}},"X"]}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"X"},{"`Word":"."}]} - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]}}} "None" - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Internal"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Internal"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"Internal"},{"`Word":"."}]} - {"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Internal"]}},"Y"]}} + {"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Internal"]}},"Y"]}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Word":"Internal."},{"`Code_span":"X"},{"`Word":"."},"`Space",{"`Word":"An"},"`Space",{"`Word":"other"},"`Space",{"`Word":"sentence."}]} - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Z"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Z"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"Z"},{"`Word":"."}]} - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"F"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"F"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"F ()"},{"`Word":"."}]} - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Type_of"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Type_of"]}}} "None" - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Type_of_str"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Type_of_str"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"of"},"`Space",{"`Code_span":"Type_of_str"},{"`Word":"."}]} - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"With_type"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"With_type"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"T"},{"`Word":"."}]} - {"`Resolved":{"`Alias":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"External"]}},"X"]},{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Alias"]}}]}} + {"`Resolved":{"`Alias":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"External"]}},"X"]},{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Alias"]}}]}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"X"},{"`Word":"."}]} - {"`Resolved":{"`Alias":[{"`Canonical":[{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Internal"]}},"C1"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"C1"]}}}]},{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"C1"]}}]}} + {"`Resolved":{"`Alias":[{"`Canonical":[{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Internal"]}},"C1"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"C1"]}}}]},{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"C1"]}}]}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"C1"},{"`Word":"."}]} - {"`Resolved":{"`Alias":[{"`Canonical":[{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Internal"]}},"C2"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"C2"]}}}]},{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"C2"]}}]}} + {"`Resolved":{"`Alias":[{"`Canonical":[{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Internal"]}},"C2"]},{"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"C2"]}}}]},{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"C2"]}}]}} "None" - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Inline_include"]}}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Inline_include"]}}} {"Some":[{"`Word":"Doc"},"`Space",{"`Word":"for"},"`Space",{"`Code_span":"T"},{"`Word":"."}]} - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Starts_with_open"]}}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Starts_with_open"]}}} {"Some":[{"`Word":"Synopsis"},"`Space",{"`Word":"of"},"`Space",{"`Code_span":"Starts_with_open"},{"`Word":"."}]} - {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]},"Resolve_synopsis"]}}} - {"Some":[{"`Word":"This"},"`Space",{"`Word":"should"},"`Space",{"`Word":"be"},"`Space",{"`Word":"resolved"},"`Space",{"`Word":"when"},"`Space",{"`Word":"included:"},"`Space",{"`Reference":[{"`Resolved":{"`Type":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]}},"Resolve_synopsis"]},"t"]}},[]]},{"`Word":"."},"`Space",{"`Word":"These"},"`Space",{"`Word":"shouldn't:"},"`Space",{"`Reference":[{"`Root":["t","`TUnknown"]},[]]},"`Space",{"`Reference":[{"`Dot":[{"`Root":["Resolve_synopsis","`TUnknown"]},"t"]},[]]}]} - {"`Resolved":{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"External"]}},"Resolve_synopsis"]}} + {"`Resolved":{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]},"Resolve_synopsis"]}}} + {"Some":[{"`Word":"This"},"`Space",{"`Word":"should"},"`Space",{"`Word":"be"},"`Space",{"`Word":"resolved"},"`Space",{"`Word":"when"},"`Space",{"`Word":"included:"},"`Space",{"`Reference":[{"`Resolved":{"`Type":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]}},"Resolve_synopsis"]},"t"]}},[]]},{"`Word":"."},"`Space",{"`Word":"These"},"`Space",{"`Word":"shouldn't:"},"`Space",{"`Reference":[{"`Root":["t","`TUnknown"]},[]]},"`Space",{"`Reference":[{"`Dot":[{"`Root":["Resolve_synopsis","`TUnknown"]},"t"]},[]]}]} + {"`Resolved":{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"External"]}},"Resolve_synopsis"]}} {"Some":[{"`Reference":[{"`Root":["t","`TUnknown"]},[]]}]} References in the synopses above should be resolved. 'External' contains a module list too: $ odoc_print external.odocl | jq -c '.. | .["`Modules"]? | select(.) | .[] | .[]' - {"`Resolved":{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]}},"Resolve_synopsis"]}} - {"Some":[{"`Word":"This"},"`Space",{"`Word":"should"},"`Space",{"`Word":"be"},"`Space",{"`Word":"resolved"},"`Space",{"`Word":"when"},"`Space",{"`Word":"included:"},"`Space",{"`Reference":[{"`Resolved":{"`Type":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Main"]}},"Resolve_synopsis"]},"t"]}},[]]},{"`Word":"."},"`Space",{"`Word":"These"},"`Space",{"`Word":"shouldn't:"},"`Space",{"`Reference":[{"`Root":["t","`TUnknown"]},[]]},"`Space",{"`Reference":[{"`Dot":[{"`Root":["Resolve_synopsis","`TUnknown"]},"t"]},[]]}]} + {"`Resolved":{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]}},"Resolve_synopsis"]}} + {"Some":[{"`Word":"This"},"`Space",{"`Word":"should"},"`Space",{"`Word":"be"},"`Space",{"`Word":"resolved"},"`Space",{"`Word":"when"},"`Space",{"`Word":"included:"},"`Space",{"`Reference":[{"`Resolved":{"`Type":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Main"]}},"Resolve_synopsis"]},"t"]}},[]]},{"`Word":"."},"`Space",{"`Word":"These"},"`Space",{"`Word":"shouldn't:"},"`Space",{"`Reference":[{"`Root":["t","`TUnknown"]},[]]},"`Space",{"`Reference":[{"`Dot":[{"`Root":["Resolve_synopsis","`TUnknown"]},"t"]},[]]}]} 'Type_of' and 'Alias' don't have a summary. `C1` and `C2` neither, we expect at least `C2` to have one. diff --git a/test/xref2/path_references.t/run.t b/test/xref2/path_references.t/run.t index 65a567faec..1c8c69f3ae 100644 --- a/test/xref2/path_references.t/run.t +++ b/test/xref2/path_references.t/run.t @@ -65,7 +65,7 @@ Helper that extracts references in a compact way. Headings help to interpret the {"`Reference":[{"`Resolved":{"`Identifier":{"`LeafPage":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"doc"]}},"subdir"]}},"dup"]}}},[]]} ["Module","Test"] {"`Reference":[{"`Any_path":["`TCurrentPackage",["Test"]]},[]]} - {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname"]}},"Test"]}}},[]]} + {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname","libname"]}},"Test"]}}},[]]} {"`Reference":[{"`Any_path":["`TRelativePath",["Test"]]},[]]} {"`Reference":[{"`Root":["Test","`TUnknown"]},[]]} ["Asset"] @@ -116,7 +116,7 @@ Helper that extracts references in a compact way. Headings help to interpret the {"`Reference":[{"`Resolved":{"`Identifier":{"`LeafPage":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"doc"]}},"subdir"]}},"dup"]}}},[]]} {"`Reference":[{"`Resolved":{"`Identifier":{"`LeafPage":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"doc"]}},"subdir"]}},"dup"]}}},[]]} ["Module","Test"] - {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname"]}},"Test"]}}},[]]} - {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname"]}},"Test"]}}},[]]} - {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname"]}},"Test"]}}},[]]} - {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname"]}},"Test"]}}},[]]} + {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname","libname"]}},"Test"]}}},[]]} + {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname","libname"]}},"Test"]}}},[]]} + {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname","libname"]}},"Test"]}}},[]]} + {"`Reference":[{"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":[{"Some":{"`Page":[{"Some":{"`Page":["None","pkg"]}},"lib"]}},"libname","libname"]}},"Test"]}}},[]]} diff --git a/test/xref2/references_scope.t/run.t b/test/xref2/references_scope.t/run.t index b2f43a982e..a763b19c75 100644 --- a/test/xref2/references_scope.t/run.t +++ b/test/xref2/references_scope.t/run.t @@ -9,27 +9,27 @@ The references from a.mli, see the attached text to recognize them: $ odoc_print a.odocl | jq_scan_references - [{"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"A"]},"B"]}},"C"]}},[{"`Word":"Defined-below"}]] - [{"`Resolved":{"`Module":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"A"]}},"B"]},"C"]}},[{"`Word":"Defined-below-but-absolute"}]] + [{"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"A"]},"B"]}},"C"]}},[{"`Word":"Defined-below"}]] + [{"`Resolved":{"`Module":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"A"]}},"B"]},"C"]}},[{"`Word":"Defined-below-but-absolute"}]] [{"`Root":["C","`TUnknown"]},[{"`Word":"Through-open"}]] - [{"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"A"]},"B"]}},"C"]}},[{"`Word":"Doc-relative"}]] - [{"`Resolved":{"`Module":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"A"]}},"B"]},"C"]}},[{"`Word":"Doc-absolute"}]] + [{"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"A"]},"B"]}},"C"]}},[{"`Word":"Doc-relative"}]] + [{"`Resolved":{"`Module":[{"`Module":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"A"]}},"B"]},"C"]}},[{"`Word":"Doc-absolute"}]] References should be resolved after the whole signature has been added to the scope. Both "Before-shadowed" and "After-shadowed" should resolve to [M.t]. $ odoc_print shadowed.odocl | jq_scan_references - [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed"]},"M"]},"t"]}}},[{"`Word":"Before-shadowed"}]] - [{"`Resolved":{"`Type":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed"]}},"t"]}},[]] - [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed"]},"M"]},"t"]}}},[{"`Word":"After-shadowed"}]] - [{"`Resolved":{"`Identifier":{"`Value":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed"]},"N"]},"f"]}}},[]] - [{"`Resolved":{"`Value":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed"]}},"f"]}},[]] + [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed"]},"M"]},"t"]}}},[{"`Word":"Before-shadowed"}]] + [{"`Resolved":{"`Type":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed"]}},"t"]}},[]] + [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed"]},"M"]},"t"]}}},[{"`Word":"After-shadowed"}]] + [{"`Resolved":{"`Identifier":{"`Value":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed"]},"N"]},"f"]}}},[]] + [{"`Resolved":{"`Value":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed"]}},"f"]}},[]] "Before-open" and "After-open" should resolve to to [T.t]. "Before-include" and "After-include" should resolve to [Through_include.t]. $ odoc_print shadowed_through_open.odocl | jq_scan_references - [{"`Resolved":{"`Identifier":{"`Type":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed_through_open"]},"t"]}}},[{"`Word":"Before-open"}]] - [{"`Resolved":{"`Identifier":{"`Type":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed_through_open"]},"t"]}}},[{"`Word":"After-open"}]] - [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed_through_open"]},"Through_include"]},"t"]}}},[{"`Word":"Before-include"}]] - [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Page":["None","test"]}},"Shadowed_through_open"]},"Through_include"]},"t"]}}},[{"`Word":"After-include"}]] + [{"`Resolved":{"`Identifier":{"`Type":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed_through_open"]},"t"]}}},[{"`Word":"Before-open"}]] + [{"`Resolved":{"`Identifier":{"`Type":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed_through_open"]},"t"]}}},[{"`Word":"After-open"}]] + [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed_through_open"]},"Through_include"]},"t"]}}},[{"`Word":"Before-include"}]] + [{"`Resolved":{"`Identifier":{"`Type":[{"`Module":[{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Shadowed_through_open"]},"Through_include"]},"t"]}}},[{"`Word":"After-include"}]] diff --git a/test/xref2/references_to_pages.t/run.t b/test/xref2/references_to_pages.t/run.t index 0b9c36cecf..ba7c1247f4 100644 --- a/test/xref2/references_to_pages.t/run.t +++ b/test/xref2/references_to_pages.t/run.t @@ -27,5 +27,5 @@ Every references in `Bad_references` should not: Every references in `P` should resolve: $ odoc_print page-p.odocl | jq_scan_references - {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_references"]}}} - {"`Resolved":{"`Type":[{"`Identifier":{"`Root":[{"Some":{"`Page":["None","test"]}},"Good_references"]}},"t"]}} + {"`Resolved":{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_references"]}}} + {"`Resolved":{"`Type":[{"`Identifier":{"`Root":[{"Some":{"`Library":["None","test","test"]}},"Good_references"]}},"t"]}} diff --git a/test/xref2/strengthen_includes.t/run.t b/test/xref2/strengthen_includes.t/run.t index 2d2da22d1c..f691794ff8 100644 --- a/test/xref2/strengthen_includes.t/run.t +++ b/test/xref2/strengthen_includes.t/run.t @@ -31,4 +31,3 @@ _not_ been strengthened. $ find html/x/Test/ZZ html/x/Test/ZZ html/x/Test/ZZ/index.html - diff --git a/test/xref2/with.t/run.t b/test/xref2/with.t/run.t index 6a633e45c9..cdad54d134 100644 --- a/test/xref2/with.t/run.t +++ b/test/xref2/with.t/run.t @@ -31,8 +31,9 @@ Let's check which module type `.content.Module.items[0].ModuleType` refers to: "`Root": [ { "Some": { - "`Page": [ + "`Library": [ "None", + "page", "page" ] } From 17118d0a29a9e69609e62367e6f7631f570b5eee Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 14:43:24 +0200 Subject: [PATCH 4/5] Show packages and libraries in the breadcrumbs This makes the breadcrumbs more readable by removing unteresting components and make the beginning of the module path more recognizable. --- src/html/generator.ml | 37 +++++++++++-------- test/integration/html_opts.t/run.t | 2 +- .../json_expansion_with_sources.t/run.t | 2 +- test/model/index_page_name.t/run.t | 2 +- .../include_module_type_of_preamble.t/run.t | 8 ++-- test/xref2/labels/labels.t/run.t | 4 +- test/xref2/module_preamble.t/run.t | 8 ++-- 7 files changed, 35 insertions(+), 28 deletions(-) diff --git a/src/html/generator.ml b/src/html/generator.ml index b40f90b16d..aacd9263d4 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -14,7 +14,10 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) module HLink = Link + +open Odoc_utils open Odoc_document.Types + module Html = Tyxml.Html module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url @@ -499,23 +502,27 @@ 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 resolve = Link.Current url in + let breadcrumb ?(prefix = "") url = + let href = Link.href ~config ~resolve (Url.from_path url) in + { href; name = prefix ^ url.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 rec package url = + match url.Url.Path.parent with + | None -> breadcrumb ~prefix:"Package " url + | Some url -> package url + in + let rec rhs (url : Url.Path.t) = + match url with + | { kind = `Library; parent; _ } -> + let package = Option.map package parent in + (* Don't list components that separates the package and library names. *) + breadcrumb ~prefix:"Library " url :: Option.to_list package + | { parent = None; kind = `Page; _ } -> [ package url ] + | { parent = None; _ } -> [ breadcrumb url ] + | { parent = Some parent; _ } -> breadcrumb url :: rhs parent in - get_parent_paths (List.rev (Odoc_document.Url.Path.to_list url)) - |> List.rev |> List.map to_breadcrumb + List.rev (rhs url) end module Page = struct diff --git a/test/integration/html_opts.t/run.t b/test/integration/html_opts.t/run.t index 984dd06609..a155fcf981 100644 --- a/test/integration/html_opts.t/run.t +++ b/test/integration/html_opts.t/run.t @@ -22,7 +22,7 @@ Generate --as-json embeddable HTML fragment output: $ odoc html-generate test.odocl -o html --as-json --indent $ cat html/test/Test/index.html.json - {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"test","href":"../index.html","kind":"library"},{"name":"Test","href":"#","kind":"module"}],"toc":[{"title":"Section 1","href":"#section-1","children":[]},{"title":"Section 2","href":"#section-2","children":[]}],"global_toc":null,"source_anchor":null,"preamble":"

Test

","content":"

Section 1

\u000A
\u000A \u000A type t\u000A
\u000A

Section 2

\u000A
\u000A \u000A type u\u000A
\u000A
"} + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Library test","href":"../index.html","kind":"library"},{"name":"Test","href":"#","kind":"module"}],"toc":[{"title":"Section 1","href":"#section-1","children":[]},{"title":"Section 2","href":"#section-2","children":[]}],"global_toc":null,"source_anchor":null,"preamble":"

Test

","content":"

Section 1

\u000A
\u000A \u000A type t\u000A
\u000A

Section 2

\u000A
\u000A \u000A type u\u000A
\u000A
"} $ odoc html-targets test.odocl -o html --as-json --indent html/test/Test/index.html.json diff --git a/test/integration/json_expansion_with_sources.t/run.t b/test/integration/json_expansion_with_sources.t/run.t index 4481715140..7fb38ceaa7 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":"
1\u000Amodule B = struct end\u000A
"} + {"type":"source","breadcrumbs":[{"name":"Package src","href":"index.html","kind":"page"},{"name":"a.ml","href":"#","kind":"source"}],"content":"
1\u000Amodule B = struct end\u000A
"} diff --git a/test/model/index_page_name.t/run.t b/test/model/index_page_name.t/run.t index 2ea0d9de6f..1ffbf6c1a9 100644 --- a/test/model/index_page_name.t/run.t +++ b/test/model/index_page_name.t/run.t @@ -13,4 +13,4 @@ The breadcrumbs shouldn't show the name of the page, "index". Expected to fail: $ grep odoc-nav test/index.html - + diff --git a/test/xref2/include_module_type_of_preamble.t/run.t b/test/xref2/include_module_type_of_preamble.t/run.t index 4f35f10805..5c3c0c2b72 100644 --- a/test/xref2/include_module_type_of_preamble.t/run.t +++ b/test/xref2/include_module_type_of_preamble.t/run.t @@ -16,7 +16,7 @@ Foo contains "Preamble for O" once.

Module Foo

Preamble for Foo.

@@ -59,7 +59,7 @@ Bar doesn't contain "Preamble for Foo" on purpose.

Module Bar

@@ -134,7 +134,7 @@ Check the preambles:
@@ -155,7 +155,7 @@ Check the preambles:
diff --git a/test/xref2/labels/labels.t/run.t b/test/xref2/labels/labels.t/run.t index 07d9eaf021..1be4c6eddf 100644 --- a/test/xref2/labels/labels.t/run.t +++ b/test/xref2/labels/labels.t/run.t @@ -52,7 +52,7 @@ There are two references in N, one should point to a local label and the other t
@@ -87,7 +87,7 @@ The second occurence of 'B' in the main page should be disambiguated

Module Test

diff --git a/test/xref2/module_preamble.t/run.t b/test/xref2/module_preamble.t/run.t index 3bc925f218..ad691ca89d 100644 --- a/test/xref2/module_preamble.t/run.t +++ b/test/xref2/module_preamble.t/run.t @@ -40,7 +40,7 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered

Module A

Module A.

@@ -78,8 +78,8 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered

Module A.B

Module B. This paragraph is the synopsis.

@@ -120,7 +120,7 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered

Module A__b

From a7aedca5e214a4dc6615460bba03460be968ab09 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 15:09:05 +0200 Subject: [PATCH 5/5] Update Changes --- CHANGES.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGES.md b/CHANGES.md index f784df393a..b6dc821121 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -31,6 +31,7 @@ - Add a 'remap' option to HTML generation for partial docsets (@jonludlam, #1189) - Added an `html-generate-asset` command (@panglesd, #1185) - Added syntax for images, videos, audio (@panglesd, #1184) +- Show packages and libraries names in breadcrumbs (@Julow, #1190) ### Changed