From 1cbe2ee9d0698a0da9237a26aaa6d91aa814fb2a Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Fri, 19 Nov 2021 13:56:00 +0000 Subject: [PATCH 01/12] Fix reporting of unexpanded module type of expressions --- src/xref2/errors.ml | 10 +++++++++- test/xref2/multi_file_module_type_of.t/run.t | 6 ++++-- test/xref2/unexpanded_module_type_of.t/run.t | 3 ++- 3 files changed, 15 insertions(+), 4 deletions(-) diff --git a/src/xref2/errors.ml b/src/xref2/errors.ml index c1aa28cc46..e4ca3a9502 100644 --- a/src/xref2/errors.ml +++ b/src/xref2/errors.ml @@ -215,6 +215,8 @@ let is_unexpanded_module_type_of = in inner +type kind = [ `OpaqueModule | `Root of string ] + let rec kind_of_module_cpath = function | `Root name -> Some (`Root name) | `Substituted p' | `Dot (p', _) -> kind_of_module_cpath p' @@ -231,11 +233,12 @@ let rec kind_of_module_type_cpath = function (** [Some (`Root _)] for errors during lookup of root modules or [None] for other errors. *) -let rec kind_of_error = function +let rec kind_of_error : Tools_error.any -> kind option = function | `UnresolvedPath (`Module (cp, _)) -> kind_of_module_cpath cp | `UnresolvedPath (`ModuleType (cp, _)) -> kind_of_module_type_cpath cp | `Lookup_failure (`Root (_, name)) -> Some (`Root (Names.ModuleName.to_string name)) + | `UnexpandedTypeOf type_of_desc -> kind_of_type_of_desc type_of_desc | `Lookup_failure_root name -> Some (`Root name) | `Parent (`Parent_sig e) -> kind_of_error (e :> Tools_error.any) | `Parent (`Parent_module_type e) -> kind_of_error (e :> Tools_error.any) @@ -247,6 +250,11 @@ let rec kind_of_error = function Some `OpaqueModule | _ -> None +and kind_of_type_of_desc : Component.ModuleType.type_of_desc -> kind option = + function + | ModPath cp -> kind_of_module_cpath cp + | StructInclude cp -> kind_of_module_cpath cp + let kind_of_error ~what = function | Some e -> kind_of_error (e :> Tools_error.any) | None -> ( diff --git a/test/xref2/multi_file_module_type_of.t/run.t b/test/xref2/multi_file_module_type_of.t/run.t index ad657ab7fe..02772ad35b 100644 --- a/test/xref2/multi_file_module_type_of.t/run.t +++ b/test/xref2/multi_file_module_type_of.t/run.t @@ -28,14 +28,16 @@ on test1.cmti: $ odoc compile --package foo test1.cmti File "test1.cmti": - Warning: Failed to compile expansion for module type expression module type of unresolvedroot(Test0) Unexpanded `module type of` expression: module type of unresolvedroot(Test0) + Warning: Couldn't find the following modules: + Test0 Similarly, module `T` also can not be expanded, therefore we expect another warning when we run `odoc compile` on test2.cmti: $ odoc compile --package foo test2.cmti -I . File "test2.cmti": - Warning: Failed to compile expansion for module type expression module type of unresolvedroot(Test1).S Unexpanded `module type of` expression: module type of unresolvedroot(Test1).S + Warning: Couldn't find the following modules: + Test1 Crucially though, we do expect this command to have terminated! diff --git a/test/xref2/unexpanded_module_type_of.t/run.t b/test/xref2/unexpanded_module_type_of.t/run.t index 56583c0606..f0449727a7 100644 --- a/test/xref2/unexpanded_module_type_of.t/run.t +++ b/test/xref2/unexpanded_module_type_of.t/run.t @@ -17,4 +17,5 @@ should _not_ result in an exception, merely a warning. $ odoc compile --package test test.cmti File "test.cmti": - Warning: Failed to compile expansion for include : module type of unresolvedroot(Test0) Unexpanded `module type of` expression: module type of unresolvedroot(Test0) + Warning: Couldn't find the following modules: + Test0 From a9defc8306ad9f9599afdddefed7b281afceb236 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Fri, 19 Nov 2021 16:03:33 +0000 Subject: [PATCH 02/12] Shuffle docs around --- doc/driver.md | 3 +-- doc/driver.mld | 3 +-- doc/dune | 2 +- doc/library_mlds/dune | 16 ++++++++++++++++ doc/library_mlds/odoc_parser.mld | 3 --- 5 files changed, 19 insertions(+), 8 deletions(-) create mode 100644 doc/library_mlds/dune delete mode 100644 doc/library_mlds/odoc_parser.mld diff --git a/doc/driver.md b/doc/driver.md index 8e6cc88600..aacb29f78a 100644 --- a/doc/driver.md +++ b/doc/driver.md @@ -29,7 +29,6 @@ let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m - `odoc/odoc_model/index.html` : `odoc` model library subpage - `odoc/odoc_model/Odoc_model/index.html` : Module page for the module `Odoc_model` - `odoc/odoc_model/Odoc_model/...` : Further pages for the submodules of `Odoc_model` -- `odoc/odoc_parser/index.html` : `odoc` parser library subpage - `odoc/odoc_.../index.html` : other `odoc` library pages - `odoc/deps/stdlib/index.html` : stdlib main page - `odoc/deps/stdlib/Stdlib/index.html` : Module page for the module `Stdlib` @@ -42,7 +41,7 @@ In the example below, there will be a file `odoc.mld` that corresponds with the ```sh -odoc compile odoc.mld --child page-odoc_model --child page-odoc_parser --child deps ... +odoc compile odoc.mld --child page-odoc_model --child deps ... ``` The file `deps.mld` which corresponds with the sub-directory `odoc/deps/`, will be compiled as follows: diff --git a/doc/driver.mld b/doc/driver.mld index fa7d060ff5..c82fcc736d 100644 --- a/doc/driver.mld +++ b/doc/driver.mld @@ -28,7 +28,6 @@ let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m }{- [odoc/odoc_model/index.html] : [odoc] model library subpage }{- [odoc/odoc_model/Odoc_model/index.html] : Module page for the module [Odoc_model] }{- [odoc/odoc_model/Odoc_model/...] : Further pages for the submodules of [Odoc_model] -}{- [odoc/odoc_parser/index.html] : [odoc] parser library subpage }{- [odoc/odoc_.../index.html] : other [odoc] library pages }{- [odoc/deps/stdlib/index.html] : stdlib main page }{- [odoc/deps/stdlib/Stdlib/index.html] : Module page for the module [Stdlib] @@ -41,7 +40,7 @@ The [odoc] model for achieving this is that we have {e pages} ([.mld] files) tha In the example below, there will be a file [odoc.mld] that corresponds with the top-level directory [odoc/]. It will be compiled as follows: {[ -odoc compile odoc.mld --child page-odoc_model --child page-odoc_parser --child deps ... +odoc compile odoc.mld --child page-odoc_model --child deps ... ]} The file [deps.mld] which corresponds with the sub-directory [odoc/deps/], will be compiled as follows: diff --git a/doc/dune b/doc/dune index 12e5667c30..7e26e2ac6b 100644 --- a/doc/dune +++ b/doc/dune @@ -1,6 +1,6 @@ (documentation (package odoc) - (mld_files contributing deps driver dune features index interface + (mld_files contributing driver dune features index interface ocamldoc_differences odoc_for_authors parent_child_spec)) (rule diff --git a/doc/library_mlds/dune b/doc/library_mlds/dune new file mode 100644 index 0000000000..169ef0f5a6 --- /dev/null +++ b/doc/library_mlds/dune @@ -0,0 +1,16 @@ +(documentation + (package odoc) + (mld_files +odoc_document +odoc_examples +odoc_html +odoc_latex +odoc_loader +odoc_manpage +odoc_model +odoc_model_desc +odoc_odoc +odoc_xref2 +odoc_xref_test)) + + diff --git a/doc/library_mlds/odoc_parser.mld b/doc/library_mlds/odoc_parser.mld deleted file mode 100644 index 5920ad0d20..0000000000 --- a/doc/library_mlds/odoc_parser.mld +++ /dev/null @@ -1,3 +0,0 @@ -{0 odoc_parser} - -{!childmodule-Odoc_parser} From 6f35c8b7aed17146ae17f0aecc873e00273a089d Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 09:41:43 +0000 Subject: [PATCH 03/12] Re-allow duplicate entries being added to the environment There's an issue somewhere meaning that sometimes shadowed items end up aren't marked as such - for example `compare` in `ocaml.git/middle_end/backend_var.mli`. Rather than turn that into a hard error just re-enable the duplication for now. --- src/xref2/env.ml | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/src/xref2/env.ml b/src/xref2/env.ml index 1de168e548..0e51f90a41 100644 --- a/src/xref2/env.ml +++ b/src/xref2/env.ml @@ -218,7 +218,13 @@ let add_to_elts kind identifier component env = assert ( List.mem kind [ Kind_Module; Kind_ModuleType; Kind_Type; Kind_Class; Kind_ClassType ]); - assert (ElementsById.find_by_id identifier env.ids = None); + let _ = + let other = ElementsById.find_by_id identifier env.ids in + match other with + | Some _ -> + Format.eprintf "Overriding duplicate env entry\n%!" + | None -> () + in let name = Identifier.name identifier in { env with From 58abcc587a3c2a196e48d4ce5b1d2fc105c058ac Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 10:02:47 +0000 Subject: [PATCH 04/12] The library mlds are dependencies of the doc generator --- doc/dune | 1 + 1 file changed, 1 insertion(+) diff --git a/doc/dune b/doc/dune index 7e26e2ac6b..0764087817 100644 --- a/doc/dune +++ b/doc/dune @@ -9,6 +9,7 @@ (:x driver.md) (glob_files *.ml*) (glob_files *.png) + (glob_files library_mlds/*.mld) (package odoc)) (enabled_if (> %{ocaml_version} 4.11)) From 93eafa5d3c2296acd0559189e9690c9031269424 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 09:50:28 +0000 Subject: [PATCH 05/12] Minor doc fixes --- doc/features.mld | 4 ++-- doc/library_mlds/odoc-parser.mld | 2 +- doc/odoc_for_authors.mld | 12 ++++++------ 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/doc/features.mld b/doc/features.mld index 44d6181cdc..9662d9e6cd 100644 --- a/doc/features.mld +++ b/doc/features.mld @@ -62,7 +62,7 @@ and the full expansion can be found by clicking on the name of the module These expansions have to be done carefully. A number of cases follow in which [odoc] has to treat specially. -{2 Aliases} +{2:expansion_aliases Aliases} In general [odoc] doesn’t expand module aliases unless they are an alias to a hidden module. If this is the case, the right-hand side of @@ -468,7 +468,7 @@ links need to consider some of the expansions’ features, as outlined above. In order to decide where the links should point to and how to turn them into text, a process called 'Resolution' is required. -{2 Aliases} +{2:resolution_aliases Aliases} Since aliases are not usually expanded, a path or reference to an item contained in an aliased module must link directly to the item inside the aliased module. For diff --git a/doc/library_mlds/odoc-parser.mld b/doc/library_mlds/odoc-parser.mld index ff4ff802ce..3505656935 100644 --- a/doc/library_mlds/odoc-parser.mld +++ b/doc/library_mlds/odoc-parser.mld @@ -1,3 +1,3 @@ -{0 Odoc_parser} +{0 Odoc-parser} The parser library used by Odoc. See {!module-Odoc_parser}. \ No newline at end of file diff --git a/doc/odoc_for_authors.mld b/doc/odoc_for_authors.mld index c4786deaaa..c9a49f9d83 100644 --- a/doc/odoc_for_authors.mld +++ b/doc/odoc_for_authors.mld @@ -36,7 +36,7 @@ v} Odoc is built to produce documentation for your {e libraries}, and the unit of organisation is the {e module}. Documentation is written by putting -{{!comments}special comments} into the source of the {e module interface} or +{{!special_comments}special comments} into the source of the {e module interface} or less commonly your {e module implementation}. For the HTML output, [odoc] will produce one page for each module, module type, @@ -67,7 +67,7 @@ it is intended that all features of the OCaml language are supported by [odoc]. For examples of how the language features are handled, see the {{!page-features}Features} page. -{2:comment-placement Comment placement} +{2:special_comments Special Comments} Comments containing documentation are known as {e special comments}. They are like normal comments except they have precisely @@ -75,7 +75,7 @@ two asterisks at the start: {[ (* Normal comment *) -(** Documentation comment *) +(** Special comment containing documentation *) (*** Normal comment *) ]} @@ -425,7 +425,7 @@ end type u ]} -The above example can be seen rendered in the module {!Odoc_examples.Scope}. +The above example can be seen rendered in the module {!Odoc_examples.Markup.Scope}. [odoc] allows modules to be 'opened' for the purposes of resolving references. By default, the module [Stdlib] is 'opened', allowing references like [{!List.t}] @@ -543,7 +543,7 @@ The OCaml manual provides an instructive example: The output of this as rendered by [odoc] is {{!Odoc_examples.Markup.Stop}here}. -{1 Page Structure} +{1:page_structure Page Structure} Producing good documentation for your library is more than simply annotating the various modules, type and functions that are contained however. @@ -645,7 +645,7 @@ Note: A comment attached to a declaration shouldn't contain any heading. The synopsis of a module (a module type, a class, etc..) is the first paragraph of the {!preamble}, {e if} the preamble starts with a paragraph. -It is rendered in [{!modules:...}] lists and after {{!page-features.aliases}expanded aliases}. +It is rendered in [{!modules:...}] lists and after {{!page-features.expansion_aliases}expanded aliases}. Note that the synopsis is computed on top of the {e preamble}, in these two examples, the synopsis is the same: From cf981b38e68c1c88c95c32f5f29d7817ced30732 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 10:14:06 +0000 Subject: [PATCH 06/12] Driver fixes Now using OCaml 4.12.1 (with lots of new reference resolution failures to report!) --- doc/driver.md | 429 +++++++++++++++++++++++++++++++++++++++++++++++-- doc/driver.mld | 26 +-- 2 files changed, 433 insertions(+), 22 deletions(-) diff --git a/doc/driver.md b/doc/driver.md index aacb29f78a..c4e25dd46b 100644 --- a/doc/driver.md +++ b/doc/driver.md @@ -14,6 +14,8 @@ First we need to initialise MDX with some libraries and helpful values. (* Prelude *) #require "bos";; #install_printer Fpath.pp;; +#print_length 100;; +#print_depth 10;; open Bos;; let (>>=) = Result.bind;; let (>>|=) m f = m >>= fun x -> Ok (f x);; @@ -159,6 +161,8 @@ let compile file ?parent ?(ignore_output = false) children = let link ?(ignore_output = false) file = let open Cmd in let cmd = odoc % "link" % p file % "-I" % "." in + let cmd = if Fpath.to_string file = "stdlib.odoc" then cmd % "--open=\"\"" else cmd in + Format.printf "%a" pp cmd; let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in if not ignore_output then add_prefixed_output cmd link_output (Fpath.to_string file) lines @@ -339,16 +343,16 @@ let odoc_units = ``` ```ocaml env=e1 -let lib_units = - List.map - (fun (lib, p) -> - Fpath.Set.fold - (fun p acc -> ("deps", lib, p) :: acc) - (find_units p |> get_ok) - []) - lib_paths - -let all_units = odoc_units @ lib_units |> List.flatten +let all_units = + let lib_units = + List.map + (fun (lib, p) -> + Fpath.Set.fold + (fun p acc -> ("deps", lib, p) :: acc) + (find_units p |> get_ok) + []) + lib_paths in + odoc_units @ lib_units |> List.flatten ``` Now we'll compile all of the parent `.mld` files. To ensure that the parents are compiled before the children, we start with `odoc.mld`, then `deps.mld`, and so on. The result of this file is a list of the resulting `odoc` files. @@ -454,10 +458,413 @@ generate_all linked Let's see if there was any output from the `odoc` invocations: ```ocaml env=e1 +# #print_length 655360;; # !compile_output;; - : string list = [""] # !link_output;; -- : string list = [""] +- : string list = +[""; "'../src/odoc/bin/main.exe' 'link' 'odoc_xref2.odoc' '-I' '.'"; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_xref2.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_xref2.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_xref2.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "'../src/odoc/bin/main.exe' 'link' 'odoc_model.odoc' '-I' '.'"; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"map.mli\", line 331, characters 16-24:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).map Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 248, characters 16-36:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 242, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_binding Couldn't find \"S\""; + "odoc_model.odoc: File \"map.mli\", line 223, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "odoc_model.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_model.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_model.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "'../src/odoc/bin/main.exe' 'link' 'odoc_examples.odoc' '-I' '.'"; + "odoc_examples.odoc: File \"set.mli\", line 208, characters 16-32:"; + "odoc_examples.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt_opt Couldn't find \"S\""; + "odoc_examples.odoc: File \"set.mli\", line 204, characters 16-28:"; + "odoc_examples.odoc: Warning: Failed to resolve reference unresolvedroot(S).min_elt Couldn't find \"S\""; + "odoc_examples.odoc: File \"set.mli\", line 189, characters 16-23:"; + "odoc_examples.odoc: Warning: Failed to resolve reference unresolvedroot(Make) Couldn't find \"Make\""; + "'../src/odoc/bin/main.exe' 'link' 'page-deps.odoc' '-I' '.'"; + "page-deps.odoc: File \"src/fmt.mli\", line 6, characters 4-13:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Format) Couldn't find \"Format\""; + "page-deps.odoc: File \"src/fpath.mli\", line 8, characters 8-20:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Map) Couldn't find \"Map\""; + "page-deps.odoc: File \"src/fpath.mli\", line 7, characters 59-71:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Set) Couldn't find \"Set\""; + "page-deps.odoc: File \"src/fpath.mli\", line 7, characters 28-52:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(file_exts) Couldn't find \"file_exts\""] # !generate_output;; - : string list = [""; diff --git a/doc/driver.mld b/doc/driver.mld index c82fcc736d..18cda78f43 100644 --- a/doc/driver.mld +++ b/doc/driver.mld @@ -14,6 +14,8 @@ First we need to initialise MDX with some libraries and helpful values. (* Prelude *) #require "bos";; #install_printer Fpath.pp;; +#print_length 100;; +#print_depth 10;; open Bos;; let (>>=) = Result.bind;; let (>>|=) m f = m >>= fun x -> Ok (f x);; @@ -156,7 +158,8 @@ let compile file ?parent ?(ignore_output = false) children = let link ?(ignore_output = false) file = let open Cmd in let cmd = odoc % "link" % p file % "-I" % "." in - let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in + let cmd = if Fpath.to_string file = "stdlib.odoc" then cmd % "--open=\"\"" else cmd in + Format.printf "%a" pp cmd;let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in if not ignore_output then add_prefixed_output cmd link_output (Fpath.to_string file) lines @@ -347,16 +350,16 @@ let odoc_units = ]} {[ -let lib_units = - List.map - (fun (lib, p) -> - Fpath.Set.fold - (fun p acc -> ("deps", lib, p) :: acc) - (find_units p |> get_ok) - []) - lib_paths - -let all_units = odoc_units @ lib_units |> List.flatten +let all_units = + let lib_units = + List.map + (fun (lib, p) -> + Fpath.Set.fold + (fun p acc -> ("deps", lib, p) :: acc) + (find_units p |> get_ok) + []) + lib_paths in + odoc_units @ lib_units |> List.flatten ]} Now we'll compile all of the parent [.mld] files. To ensure that the parents are compiled before the children, we start with [odoc.mld], then [deps.mld], and so on. The result of this file is a list of the resulting [odoc] files. @@ -463,6 +466,7 @@ generate_all linked Let's see if there was any output from the [odoc] invocations: {[ +# #print_length 655360;; # !compile_output;; - : string list = [""] # !link_output;; From 21571b6914655768365959ef77f0ee4f2aa03758 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 18:25:13 +0000 Subject: [PATCH 07/12] Move a broken bit of Ocamlary into a test --- src/ocamlary/ocamlary.mli | 6 +-- .../Ocamlary-CanonicalTest-Base_Tests.html | 12 ----- test/generators/html/Ocamlary.html | 45 ++++++----------- test/generators/latex/Ocamlary.tex | 10 ++-- test/generators/man/Ocamlary.3o | 3 -- .../man/Ocamlary.CanonicalTest.Base_Tests.3o | 11 ----- test/xref2/hidden_modules.t/run.t | 49 +++++++++++++++++++ test/xref2/hidden_modules.t/test.mli | 30 ++++++++++++ 8 files changed, 100 insertions(+), 66 deletions(-) create mode 100644 test/xref2/hidden_modules.t/run.t create mode 100644 test/xref2/hidden_modules.t/test.mli diff --git a/src/ocamlary/ocamlary.mli b/src/ocamlary/ocamlary.mli index 23e577d29c..76ac2405f7 100644 --- a/src/ocamlary/ocamlary.mli +++ b/src/ocamlary/ocamlary.mli @@ -886,17 +886,17 @@ module CanonicalTest : sig val foo : int L.t -> float L.t val bar : 'a List.t -> 'a List.t - (** This is just {!List.id}, or rather {!L.id} *) + (* This is just {!List.id}, or rather {!L.id} *) val baz : 'a Base__.List.t -> unit - (** We can't reference [Base__] because it's hidden. + (* We can't reference [Base__] because it's hidden. {!List.t} ([List.t]) should resolve. *) end module List_modif : module type of Base.List with type 'c t = 'c Base__.List.t end -val test : 'a CanonicalTest.Base__.List.t -> unit +(* val test : 'a CanonicalTest.Base__.List.t -> unit *) (** Some ref to {!CanonicalTest.Base_Tests.C.t} and {!CanonicalTest.Base_Tests.L.id}. But also to {!CanonicalTest.Base.List} and {!CanonicalTest.Base.List.t} *) diff --git a/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html b/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html index 895d99723c..7b5568b8d1 100644 --- a/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html +++ b/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html @@ -73,13 +73,6 @@

Module CanonicalTest.Base_Tests

-
-

This is just List.id, or rather - - L.id - -

-
@@ -95,11 +88,6 @@

Module CanonicalTest.Base_Tests

-
-

We can't reference Base__ because it's hidden. - List.t (List.t) should resolve. -

-
diff --git a/test/generators/html/Ocamlary.html b/test/generators/html/Ocamlary.html index 7986a444c9..7902fbe371 100644 --- a/test/generators/html/Ocamlary.html +++ b/test/generators/html/Ocamlary.html @@ -2780,37 +2780,20 @@

-
-
- - - val test : - - 'a - CanonicalTest.Base__.List - .t - -> - unit - - -
- -
+

Some ref to + + CanonicalTest.Base_Tests.C.t + and + + CanonicalTest.Base_Tests.L.id + . But also to + + CanonicalTest.Base.List + and + + CanonicalTest.Base.List.t + +

Aliases again

diff --git a/test/generators/latex/Ocamlary.tex b/test/generators/latex/Ocamlary.tex index 7262f64cae..0191945b33 100644 --- a/test/generators/latex/Ocamlary.tex +++ b/test/generators/latex/Ocamlary.tex @@ -778,17 +778,15 @@ \subsection{Playing with @canonical paths\label{playing-with-@canonical-paths}}% \label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base+u+Tests]{\ocamlinlinecode{Base\_\allowbreak{}Tests}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}}}\\ \label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L = \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}}}\\ \label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{L.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} float \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{L.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\begin{ocamlindent}This is just \ocamlinlinecode{List}.id, or rather \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id]{\ocamlinlinecode{\ocamlinlinecode{L.\allowbreak{}id}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id}]}\end{ocamlindent}% -\medbreak -\label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-val-baz}\ocamlcodefragment{\ocamltag{keyword}{val} baz : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}We can't reference \ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}} because it's hidden. \ocamlinlinecode{List}.t (\ocamlinlinecode{List.\allowbreak{}t}) should resolve.\end{ocamlindent}% -\medbreak +\label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\ +\label{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-val-baz}\ocamlcodefragment{\ocamltag{keyword}{val} baz : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \label{module-Ocamlary-module-CanonicalTest-module-List+u+modif}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-List+u+modif]{\ocamlinlinecode{List\_\allowbreak{}modif}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} 'c \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{t}} = \ocamltag{type-var}{'c} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-val-test}\ocamlcodefragment{\ocamltag{keyword}{val} test : \ocamltag{type-var}{'a} \hyperref[xref-unresolved]{\ocamlinlinecode{CanonicalTest}}.\allowbreak{}Base\_\allowbreak{}\_\allowbreak{}.\allowbreak{}List.\allowbreak{}t \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Some ref to \hyperref[module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-C-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}C.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-C-type-t}]} and \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}L.\allowbreak{}id}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id}]}. But also to \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List}]} and \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t}]}\end{ocamlindent}% -\medbreak +Some ref to \hyperref[module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-C-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}C.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base+u+Tests-module-C-type-t}]} and \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}L.\allowbreak{}id}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id}]}. But also to \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List}]} and \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t}]} + \subsection{Aliases again\label{aliases}}% \label{module-Ocamlary-module-Aliases}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases]{\ocamlinlinecode{Aliases}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \label{module-Ocamlary-module-Aliases-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ diff --git a/test/generators/man/Ocamlary.3o b/test/generators/man/Ocamlary.3o index c67282403b..7ab3e457bf 100644 --- a/test/generators/man/Ocamlary.3o +++ b/test/generators/man/Ocamlary.3o @@ -1770,10 +1770,7 @@ With odoc, everything should be resolved (and linked) but only toplevel units wi .sp \f[CB]module\fR CanonicalTest : \f[CB]sig\fR \.\.\. \f[CB]end\fR .sp -\f[CB]val\fR test : \f[CB]'a\fR CanonicalTest\.Base__\.List\.t \f[CB]\->\fR unit .fi -.br -.ti +2 Some ref to \f[CI]CanonicalTest\.Base_Tests\.C\.t\fR and \f[CI]CanonicalTest\.Base_Tests\.L\.id\fR\. But also to \f[CI]CanonicalTest\.Base\.List\fR and \f[CI]CanonicalTest\.Base\.List\.t\fR .nf .sp diff --git a/test/generators/man/Ocamlary.CanonicalTest.Base_Tests.3o b/test/generators/man/Ocamlary.CanonicalTest.Base_Tests.3o index 0bfeac1d78..4ea66ca095 100644 --- a/test/generators/man/Ocamlary.CanonicalTest.Base_Tests.3o +++ b/test/generators/man/Ocamlary.CanonicalTest.Base_Tests.3o @@ -18,16 +18,5 @@ Ocamlary\.CanonicalTest\.Base_Tests \f[CB]val\fR foo : int L\.t \f[CB]\->\fR float L\.t .sp \f[CB]val\fR bar : \f[CB]'a\fR Base\.List\.t \f[CB]\->\fR \f[CB]'a\fR Base\.List\.t -.fi -.br -.ti +2 -This is just List\.id, or rather \f[CI]L\.id\fR -.nf .sp \f[CB]val\fR baz : \f[CB]'a\fR Base\.List\.t \f[CB]\->\fR unit -.fi -.br -.ti +2 -We can't reference Base__ because it's hidden\. List\.t (List\.t) should resolve\. -.nf - diff --git a/test/xref2/hidden_modules.t/run.t b/test/xref2/hidden_modules.t/run.t new file mode 100644 index 0000000000..8073e68412 --- /dev/null +++ b/test/xref2/hidden_modules.t/run.t @@ -0,0 +1,49 @@ +This is an excerpt from ocamlary, showing an issue resolving hidden modules that +aren't roots. + $ cat test.mli + module CanonicalTest : sig + module Base__List : sig + type 'a t + + val id : 'a t -> 'a t + end + + module Base__ : sig + module List = Base__List + (** @canonical Test.CanonicalTest.Base.List *) + end + + module Base : sig + module List = Base__.List + end + + module Base_Tests : sig + module C : module type of Base__.List + + open Base__ + module L = List + + val baz : 'a Base__.List.t -> unit + (** We can't reference [Base__] because it's hidden. + {!List.t} ([List.t]) should resolve. *) + end + end + + val test : 'a CanonicalTest.Base__.List.t -> unit + + + + $ ocamlc -c -bin-annot test.mli + $ odoc compile test.cmti + +This shouldn't cause any warnings: + + $ odoc link test.odoc -I . + File "test.odoc": + Warning: Failed to lookup type identifier((root Test).CanonicalTest, false).Base__.List.t Parent_module: Parent_module: Find failure + File "test.mli", line 25, characters 8-17: + Warning: Failed to resolve reference unresolvedroot(List).t Couldn't find "List" + + + + diff --git a/test/xref2/hidden_modules.t/test.mli b/test/xref2/hidden_modules.t/test.mli new file mode 100644 index 0000000000..5f6be2e664 --- /dev/null +++ b/test/xref2/hidden_modules.t/test.mli @@ -0,0 +1,30 @@ +module CanonicalTest : sig + module Base__List : sig + type 'a t + + val id : 'a t -> 'a t + end + + module Base__ : sig + module List = Base__List + (** @canonical Test.CanonicalTest.Base.List *) + end + + module Base : sig + module List = Base__.List + end + + module Base_Tests : sig + module C : module type of Base__.List + + open Base__ + module L = List + + val baz : 'a Base__.List.t -> unit + (** We can't reference [Base__] because it's hidden. + {!List.t} ([List.t]) should resolve. *) + end +end + +val test : 'a CanonicalTest.Base__.List.t -> unit + From b2cd38190b6067f6ade43d6a0370bceb6a6f2a30 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 18:25:36 +0000 Subject: [PATCH 08/12] Remove a duplicated label --- test/generators/cases/labels.mli | 17 +++++++++-------- test/generators/html/Labels-class-c.html | 4 ++-- .../generators/html/Labels-class-type-cs.html | 4 ++-- test/generators/html/Labels.html | 17 +++++++++-------- test/generators/latex/Labels.c.tex | 2 +- test/generators/latex/Labels.tex | 19 ++++++++++--------- test/generators/man/Labels.3o | 2 ++ 7 files changed, 35 insertions(+), 30 deletions(-) diff --git a/test/generators/cases/labels.mli b/test/generators/cases/labels.mli index f180a63deb..7bf29e0c94 100644 --- a/test/generators/cases/labels.mli +++ b/test/generators/cases/labels.mli @@ -18,28 +18,28 @@ module type S = sig end (** {1:L6 Attached to module type} *) class c : object end -(** {1:L6 Attached to class} *) +(** {1:L7 Attached to class} *) class type cs = object end -(** {1:L7 Attached to class type} *) +(** {1:L8 Attached to class type} *) exception E -(** {1:L8 Attached to exception} *) +(** {1:L9 Attached to exception} *) type x = .. -(** {1:L9 Attached to extension} *) +(** {1:L10 Attached to extension} *) type x += X module S := A -(** {1:L10 Attached to module subst} *) +(** {1:L11 Attached to module subst} *) type s := t -(** {1:L11 Attached to type subst} *) +(** {1:L12 Attached to type subst} *) -type u = A' (** {1:L12 Attached to constructor} *) +type u = A' (** {1:L13 Attached to constructor} *) -type v = { f : t (** {1:L13 Attached to field} *) } +type v = { f : t (** {1:L14 Attached to field} *) } (** Testing that labels can be referenced - {!L1} @@ -55,4 +55,5 @@ type v = { f : t (** {1:L13 Attached to field} *) } - {!L11} - {!L12} - {!L13} + - {!L14} *) diff --git a/test/generators/html/Labels-class-c.html b/test/generators/html/Labels-class-c.html index bb78a6f93c..2823977656 100644 --- a/test/generators/html/Labels-class-c.html +++ b/test/generators/html/Labels-class-c.html @@ -13,10 +13,10 @@

Class Labels.c

-
diff --git a/test/generators/latex/Labels.c.tex b/test/generators/latex/Labels.c.tex index 0f809061fd..097f1f5b3e 100644 --- a/test/generators/latex/Labels.c.tex +++ b/test/generators/latex/Labels.c.tex @@ -1,4 +1,4 @@ \section{Class \ocamlinlinecode{Labels.\allowbreak{}c}}\label{module-Labels-class-c}% -\subsection{Attached to class\label{L6}}% +\subsection{Attached to class\label{L7}}% diff --git a/test/generators/latex/Labels.tex b/test/generators/latex/Labels.tex index 6f16c446e4..c1d81a3cf5 100644 --- a/test/generators/latex/Labels.tex +++ b/test/generators/latex/Labels.tex @@ -14,7 +14,7 @@ \subsection{Attached to nothing\label{L2}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \label{module-Labels-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Labels-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L7}}% +\label{module-Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L8}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \label{module-Labels-exception-E}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{E}}\begin{ocamlindent}Attached to exception\end{ocamlindent}% @@ -46,13 +46,14 @@ \subsection{Attached to nothing\label{L2}}% \item{\hyperref[module-Labels-L3]{\ocamlinlinecode{Attached to module}[p\pageref*{module-Labels-L3}]}}% \item{\hyperref[module-Labels-L4]{\ocamlinlinecode{Attached to type}[p\pageref*{module-Labels-L4}]}}% \item{\hyperref[module-Labels-L5]{\ocamlinlinecode{Attached to value}[p\pageref*{module-Labels-L5}]}}% -\item{\hyperref[module-Labels-L6]{\ocamlinlinecode{Attached to class}[p\pageref*{module-Labels-L6}]}}% -\item{\hyperref[module-Labels-L7]{\ocamlinlinecode{Attached to class type}[p\pageref*{module-Labels-L7}]}}% -\item{\hyperref[module-Labels-L8]{\ocamlinlinecode{Attached to exception}[p\pageref*{module-Labels-L8}]}}% -\item{\hyperref[module-Labels-L9]{\ocamlinlinecode{Attached to extension}[p\pageref*{module-Labels-L9}]}}% -\item{\hyperref[module-Labels-L10]{\ocamlinlinecode{Attached to module subst}[p\pageref*{module-Labels-L10}]}}% -\item{\hyperref[module-Labels-L11]{\ocamlinlinecode{Attached to type subst}[p\pageref*{module-Labels-L11}]}}% -\item{\hyperref[module-Labels-L12]{\ocamlinlinecode{Attached to constructor}[p\pageref*{module-Labels-L12}]}}% -\item{\hyperref[module-Labels-L13]{\ocamlinlinecode{Attached to field}[p\pageref*{module-Labels-L13}]}}\end{itemize}% +\item{\hyperref[module-Labels-L6]{\ocamlinlinecode{Attached to module type}[p\pageref*{module-Labels-L6}]}}% +\item{\hyperref[module-Labels-L7]{\ocamlinlinecode{Attached to class}[p\pageref*{module-Labels-L7}]}}% +\item{\hyperref[module-Labels-L8]{\ocamlinlinecode{Attached to class type}[p\pageref*{module-Labels-L8}]}}% +\item{\hyperref[module-Labels-L9]{\ocamlinlinecode{Attached to exception}[p\pageref*{module-Labels-L9}]}}% +\item{\hyperref[module-Labels-L10]{\ocamlinlinecode{Attached to extension}[p\pageref*{module-Labels-L10}]}}% +\item{\hyperref[module-Labels-L11]{\ocamlinlinecode{Attached to module subst}[p\pageref*{module-Labels-L11}]}}% +\item{\hyperref[module-Labels-L12]{\ocamlinlinecode{Attached to type subst}[p\pageref*{module-Labels-L12}]}}% +\item{\hyperref[module-Labels-L13]{\ocamlinlinecode{Attached to constructor}[p\pageref*{module-Labels-L13}]}}% +\item{\hyperref[module-Labels-L14]{\ocamlinlinecode{Attached to field}[p\pageref*{module-Labels-L14}]}}\end{itemize}% \input{Labels.c.tex} diff --git a/test/generators/man/Labels.3o b/test/generators/man/Labels.3o index 8b5f3fc756..da49e51e7c 100644 --- a/test/generators/man/Labels.3o +++ b/test/generators/man/Labels.3o @@ -135,6 +135,8 @@ Testing that labels can be referenced .br \(bu \f[CI]Attached to value\fR .br +\(bu \f[CI]Attached to module type\fR +.br \(bu \f[CI]Attached to class\fR .br \(bu \f[CI]Attached to class type\fR From e5b41694cfab918a07427abc0b5401989a6f7ab4 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Tue, 23 Nov 2021 21:30:58 +0000 Subject: [PATCH 09/12] Add CHANGES entries for some recent changes --- CHANGES.md | 3 +++ 1 file changed, 3 insertions(+) diff --git a/CHANGES.md b/CHANGES.md index 9374c5c2ce..363ead9565 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -4,9 +4,12 @@ Unreleased Bugs fixed - Man page renderer fails to output pages that have children (@jonludlam, @Julow, #766) - Fix resolution of unprefixed references to pages (@Julow, #755) +- Fix reporting of ambiguous labels (@Julow, @jonludlam, #773, #781) +- Allow referencing of labels in the top comment (@jonludlam, #771) Additions - Strip unquoted spaces in identifiers for a more flexible reference syntax (@lubega-simon, @panglesd, #783) +- Add context to messages raised in expansions of includes (@Julow, #780) 2.0.0 ----- From 1beca0563da998736d35da692aa2d06996dc1a14 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Wed, 24 Nov 2021 00:06:22 +0000 Subject: [PATCH 10/12] Improve errors more --- src/xref2/errors.ml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/xref2/errors.ml b/src/xref2/errors.ml index e4ca3a9502..55469d03b7 100644 --- a/src/xref2/errors.ml +++ b/src/xref2/errors.ml @@ -234,8 +234,8 @@ let rec kind_of_module_type_cpath = function (** [Some (`Root _)] for errors during lookup of root modules or [None] for other errors. *) let rec kind_of_error : Tools_error.any -> kind option = function - | `UnresolvedPath (`Module (cp, _)) -> kind_of_module_cpath cp - | `UnresolvedPath (`ModuleType (cp, _)) -> kind_of_module_type_cpath cp + | `UnresolvedPath (`Module (cp, e)) -> (match kind_of_module_cpath cp with | None -> kind_of_error (e :> Tools_error.any) | x -> x) + | `UnresolvedPath (`ModuleType (cp, e)) -> (match kind_of_module_type_cpath cp with | None -> kind_of_error (e :> Tools_error.any) | x -> x) | `Lookup_failure (`Root (_, name)) -> Some (`Root (Names.ModuleName.to_string name)) | `UnexpandedTypeOf type_of_desc -> kind_of_type_of_desc type_of_desc From 20b1696044a8affef89ba978831a5f43579d278c Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Wed, 24 Nov 2021 00:08:13 +0000 Subject: [PATCH 11/12] Disable noisy warning But leave it there because it indicates a problem! --- src/xref2/env.ml | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/xref2/env.ml b/src/xref2/env.ml index 0e51f90a41..b283a6754a 100644 --- a/src/xref2/env.ml +++ b/src/xref2/env.ml @@ -222,7 +222,8 @@ let add_to_elts kind identifier component env = let other = ElementsById.find_by_id identifier env.ids in match other with | Some _ -> - Format.eprintf "Overriding duplicate env entry\n%!" + (* Format.eprintf "Overriding duplicate env entry\n%!" *) + () | None -> () in let name = Identifier.name identifier in From 9103f133d2ade0a17e9581bba2434b52d2d51d0f Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Wed, 24 Nov 2021 15:23:38 +0000 Subject: [PATCH 12/12] Formatting --- doc/library_mlds/dune | 17 +++-------------- src/xref2/env.ml | 4 ++-- src/xref2/errors.ml | 10 ++++++++-- 3 files changed, 13 insertions(+), 18 deletions(-) diff --git a/doc/library_mlds/dune b/doc/library_mlds/dune index 169ef0f5a6..da4ce76eff 100644 --- a/doc/library_mlds/dune +++ b/doc/library_mlds/dune @@ -1,16 +1,5 @@ (documentation (package odoc) - (mld_files -odoc_document -odoc_examples -odoc_html -odoc_latex -odoc_loader -odoc_manpage -odoc_model -odoc_model_desc -odoc_odoc -odoc_xref2 -odoc_xref_test)) - - + (mld_files odoc_document odoc_examples odoc_html odoc_latex odoc_loader + odoc_manpage odoc_model odoc_model_desc odoc_odoc odoc_xref2 + odoc_xref_test)) diff --git a/src/xref2/env.ml b/src/xref2/env.ml index b283a6754a..5075c9bdb8 100644 --- a/src/xref2/env.ml +++ b/src/xref2/env.ml @@ -222,8 +222,8 @@ let add_to_elts kind identifier component env = let other = ElementsById.find_by_id identifier env.ids in match other with | Some _ -> - (* Format.eprintf "Overriding duplicate env entry\n%!" *) - () + (* Format.eprintf "Overriding duplicate env entry\n%!" *) + () | None -> () in let name = Identifier.name identifier in diff --git a/src/xref2/errors.ml b/src/xref2/errors.ml index 55469d03b7..a39a7040e6 100644 --- a/src/xref2/errors.ml +++ b/src/xref2/errors.ml @@ -234,8 +234,14 @@ let rec kind_of_module_type_cpath = function (** [Some (`Root _)] for errors during lookup of root modules or [None] for other errors. *) let rec kind_of_error : Tools_error.any -> kind option = function - | `UnresolvedPath (`Module (cp, e)) -> (match kind_of_module_cpath cp with | None -> kind_of_error (e :> Tools_error.any) | x -> x) - | `UnresolvedPath (`ModuleType (cp, e)) -> (match kind_of_module_type_cpath cp with | None -> kind_of_error (e :> Tools_error.any) | x -> x) + | `UnresolvedPath (`Module (cp, e)) -> ( + match kind_of_module_cpath cp with + | None -> kind_of_error (e :> Tools_error.any) + | x -> x) + | `UnresolvedPath (`ModuleType (cp, e)) -> ( + match kind_of_module_type_cpath cp with + | None -> kind_of_error (e :> Tools_error.any) + | x -> x) | `Lookup_failure (`Root (_, name)) -> Some (`Root (Names.ModuleName.to_string name)) | `UnexpandedTypeOf type_of_desc -> kind_of_type_of_desc type_of_desc