Skip to content

Commit

Permalink
Make tests more reproducible
Browse files Browse the repository at this point in the history
Also contains a fix for source-id - currently a source id requires a
container page as parent. This was previously 'working' by creating
a parent page called "./" which is obviously not great. This change
requires that the source id have a non-empty parent, which we may want
to change at some point.
  • Loading branch information
jonludlam committed May 21, 2024
1 parent 3e34177 commit f2014c2
Show file tree
Hide file tree
Showing 17 changed files with 183 additions and 178 deletions.
12 changes: 9 additions & 3 deletions src/loader/odoc_loader.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,10 @@ let read_cmti ~make_root ~parent ~filename () =
match cmt_info.cmt_interface_digest with
| None -> raise Corrupted
| Some digest as interface ->
Odoc_model.Names.set_unique_ident (Digest.to_hex digest);
let _ =
try Odoc_model.Names.set_unique_ident (Digest.to_hex digest)
with _ -> ()
in
let name = cmt_info.cmt_modname in
let sourcefile =
( cmt_info.cmt_sourcefile,
Expand All @@ -134,7 +137,9 @@ let read_cmt ~make_root ~parent ~filename () =
let interface = cmt_info.cmt_interface_digest in
(match cmt_info.cmt_interface_digest with
| None -> raise Corrupted
| Some digest -> Odoc_model.Names.set_unique_ident (Digest.to_hex digest));
| Some digest -> (
try Odoc_model.Names.set_unique_ident (Digest.to_hex digest)
with _ -> ()));
let imports = cmt_info.cmt_imports in
match cmt_info.cmt_annots with
| Packed (_, files) ->
Expand Down Expand Up @@ -205,7 +210,8 @@ let read_impl ~make_root ~filename ~source_id () =
| None -> raise Corrupted
| exception Not_found -> raise Corrupted)
in
Odoc_model.Names.set_unique_ident (Digest.to_hex digest);
Odoc_model.Names.set_unique_ident
(Odoc_model.Paths.Identifier.fullname source_id |> String.concat "-");
let root =
match make_root ~module_name:name ~digest with
| Ok root -> root
Expand Down
13 changes: 11 additions & 2 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,10 @@ end = struct
file |> Fs.File.basename |> Fs.File.to_string
|> Astring.String.is_prefix ~affix:"page-"

let unique_id =
let doc = "For debugging use" in
Arg.(value & opt (some string) None & info ~doc ~docv:"ID" [ "unique-id" ])

let output_file ~dst ~input =
match dst with
| Some file ->
Expand All @@ -175,8 +179,13 @@ end = struct

let compile hidden directories resolve_fwd_refs dst output_dir package_opt
parent_name_opt parent_id_opt open_modules children input warnings_options
=
unique_id =
let open Or_error in
let _ =
match unique_id with
| Some id -> Odoc_model.Names.set_unique_ident id
| None -> ()
in
let resolver =
Resolver.create ~important_digests:(not resolve_fwd_refs) ~directories
~open_modules
Expand Down Expand Up @@ -262,7 +271,7 @@ end = struct
const handle_error
$ (const compile $ hidden $ odoc_file_directories $ resolve_fwd_refs $ dst
$ output_dir $ package_opt $ parent_opt $ parent_id_opt $ open_modules
$ children $ input $ warnings_options))
$ children $ input $ warnings_options $ unique_id))

let info ~docs =
let man =
Expand Down
32 changes: 18 additions & 14 deletions src/odoc/source.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,17 +21,21 @@ let root_of_implementation ~source_id ~module_name ~digest =

let compile ~resolver ~output ~warnings_options ~source_id input =
let parent_id, name = Fpath.(split_base (v source_id)) in
let parent = Compile.mk_id Fpath.(to_string (rem_empty_seg parent_id)) in
let source_id =
Paths.Identifier.Mk.source_page (parent, [ Fpath.to_string name ])
in
let make_root = root_of_implementation ~source_id in
let result =
Error.catch_errors_and_warnings (fun () ->
resolve_and_substitute ~resolver ~make_root ~source_id input)
in
(* Extract warnings to write them into the output file *)
let _, warnings = Error.unpack_warnings result in
Error.handle_errors_and_warnings ~warnings_options result >>= fun impl ->
Odoc_file.save_impl output ~warnings impl;
Ok ()
if parent_id = Fpath.v "./" then
Error (`Msg "Source id cannot be in the root directory")
else
let parent = Compile.mk_id Fpath.(to_string (rem_empty_seg parent_id)) in

let source_id =
Paths.Identifier.Mk.source_page (parent, [ Fpath.to_string name ])
in
let make_root = root_of_implementation ~source_id in
let result =
Error.catch_errors_and_warnings (fun () ->
resolve_and_substitute ~resolver ~make_root ~source_id input)
in
(* Extract warnings to write them into the output file *)
let _, warnings = Error.unpack_warnings result in
Error.handle_errors_and_warnings ~warnings_options result >>= fun impl ->
Odoc_file.save_impl output ~warnings impl;
Ok ()
22 changes: 11 additions & 11 deletions test/integration/json_expansion_with_sources.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,9 @@ Test the JSON output in the presence of expanded modules.

$ ocamlc -c -bin-annot -o main__A.cmo a.ml -I .
$ ocamlc -c -bin-annot main.ml -I .
$ odoc compile-impl --source-id a.ml -I . main__A.cmt --output-dir .
$ odoc compile-impl --source-id src/a.ml -I . main__A.cmt --output-dir .
$ odoc compile -I . main__A.cmt
$ odoc compile-impl --source-id main.ml -I . main.cmt --output-dir .
$ odoc compile-impl --source-id src/main.ml -I . main.cmt --output-dir .
$ odoc compile -I . main.cmt
$ odoc link -I . impl-main__A.odoc
$ odoc link -I . impl-main.odoc
Expand All @@ -24,27 +24,27 @@ Test the JSON output in the presence of expanded modules.
html/Main/A/index.html.json
html/Main/A/B/index.html.json
$ odoc html-targets --source a.ml -o html impl-main__A.odocl
html/a.ml.html
html/src/a.ml.html
$ odoc html-targets --source main.ml -o html impl-main.odocl
html/main.ml.html
html/src/main.ml.html
$ odoc html-targets --source a.ml --as-json -o html impl-main__A.odocl
html/a.ml.html.json
html/src/a.ml.html.json
$ odoc html-targets --source main.ml --as-json -o html impl-main.odocl
html/main.ml.html.json
html/src/main.ml.html.json

$ odoc html-generate --source a.ml --as-json -o html impl-main__A.odocl
$ odoc html-generate --as-json -o html main__A.odocl
$ odoc html-generate --source main.ml --as-json -o html impl-main.odocl
$ odoc html-generate --as-json -o html main.odocl

$ cat html/Main/index.html.json
{"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"#","kind":"module"}],"toc":[],"source_anchor":".././main.ml.html","preamble":"","content":"<div class=\"odoc-spec\"><div class=\"spec module anchored\" id=\"module-A\"><a href=\"#module-A\" class=\"anchor\"></a><a href=\".././a.ml.html\" class=\"source_link\">Source</a><code><span><span class=\"keyword\">module</span> <a href=\"A/index.html\">A</a></span><span> : <span class=\"keyword\">sig</span> ... <span class=\"keyword\">end</span></span></code></div></div>"}
{"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"#","kind":"module"}],"toc":[],"source_anchor":"../src/main.ml.html","preamble":"","content":"<div class=\"odoc-spec\"><div class=\"spec module anchored\" id=\"module-A\"><a href=\"#module-A\" class=\"anchor\"></a><a href=\"../src/a.ml.html\" class=\"source_link\">Source</a><code><span><span class=\"keyword\">module</span> <a href=\"A/index.html\">A</a></span><span> : <span class=\"keyword\">sig</span> ... <span class=\"keyword\">end</span></span></code></div></div>"}

$ cat html/Main/A/index.html.json
{"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../index.html","kind":"module"},{"name":"A","href":"#","kind":"module"}],"toc":[],"source_anchor":"../.././a.ml.html","preamble":"","content":"<div class=\"odoc-spec\"><div class=\"spec module anchored\" id=\"module-B\"><a href=\"#module-B\" class=\"anchor\"></a><a href=\"../.././a.ml.html#module-B\" class=\"source_link\">Source</a><code><span><span class=\"keyword\">module</span> <a href=\"B/index.html\">B</a></span><span> : <span class=\"keyword\">sig</span> ... <span class=\"keyword\">end</span></span></code></div></div>"}
{"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../index.html","kind":"module"},{"name":"A","href":"#","kind":"module"}],"toc":[],"source_anchor":"../../src/a.ml.html","preamble":"","content":"<div class=\"odoc-spec\"><div class=\"spec module anchored\" id=\"module-B\"><a href=\"#module-B\" class=\"anchor\"></a><a href=\"../../src/a.ml.html#module-B\" class=\"source_link\">Source</a><code><span><span class=\"keyword\">module</span> <a href=\"B/index.html\">B</a></span><span> : <span class=\"keyword\">sig</span> ... <span class=\"keyword\">end</span></span></code></div></div>"}

$ cat html/Main/A/B/index.html.json
{"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":[],"source_anchor":"../../.././a.ml.html#module-B","preamble":"","content":""}
{"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":[],"source_anchor":"../../../src/a.ml.html#module-B","preamble":"","content":""}

$ cat html/a.ml.html.json
{"type":"source","breadcrumbs":[{"name":".","href":"index.html","kind":"page"},{"name":"a.ml","href":"#","kind":"source"}],"content":"<pre class=\"source_container\"><code class=\"source_line_column\"><a id=\"L1\" class=\"source_line\" href=\"#L1\">1</a>\u000A</code><code class=\"source_code\"><span><span id=\"module-B\"><span class=\"MODULE\">module</span> <span class=\"UIDENT\">B</span> <span class=\"EQUAL\">=</span> <span class=\"STRUCT\">struct</span> <span class=\"END\">end</span></span><span class=\"EOL\">\u000A</span></span></code></pre>"}
$ cat html/src/a.ml.html.json
{"type":"source","breadcrumbs":[{"name":"src","href":"index.html","kind":"page"},{"name":"a.ml","href":"#","kind":"source"}],"content":"<pre class=\"source_container\"><code class=\"source_line_column\"><a id=\"L1\" class=\"source_line\" href=\"#L1\">1</a>\u000A</code><code class=\"source_code\"><span><span id=\"module-B\"><span class=\"MODULE\">module</span> <span class=\"UIDENT\">B</span> <span class=\"EQUAL\">=</span> <span class=\"STRUCT\">struct</span> <span class=\"END\">end</span></span><span class=\"EOL\">\u000A</span></span></code></pre>"}
10 changes: 5 additions & 5 deletions test/occurrences/double_wrapped.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -12,11 +12,11 @@ The module B depends on both B and C, the module C only depends on A.

Collecting occurrences is done on implementation files.

$ odoc compile-impl --source-id a.ml -I . main__A.cmt --output-dir .
$ odoc compile-impl --source-id c.ml -I . main__C.cmt --output-dir .
$ odoc compile-impl --source-id b.ml -I . main__B.cmt --output-dir .
$ odoc compile-impl --source-id main__.ml -I . main__.cmt --output-dir .
$ odoc compile-impl --source-id main.ml -I . main.cmt --output-dir .
$ odoc compile-impl --source-id src/a.ml -I . main__A.cmt --output-dir .
$ odoc compile-impl --source-id src/c.ml -I . main__C.cmt --output-dir .
$ odoc compile-impl --source-id src/b.ml -I . main__B.cmt --output-dir .
$ odoc compile-impl --source-id src/main__.ml -I . main__.cmt --output-dir .
$ odoc compile-impl --source-id src/main.ml -I . main.cmt --output-dir .

We need the interface version to resolve the occurrences

Expand Down
15 changes: 8 additions & 7 deletions test/sources/double_wrapped.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,11 @@ Similar to the lookup_def_wrapped test.
$ ocamlc -c -o main__.cmo main__.ml -bin-annot -I .
$ ocamlc -c -open Main__ main.ml -bin-annot -I .

$ odoc compile-impl --source-id a.ml -I . main__A.cmt --output-dir .
$ odoc compile-impl --source-id src/a.ml -I . main__A.cmt --output-dir .
$ odoc compile -I . main__A.cmt
$ odoc compile-impl --source-id main__.ml -I . main__.cmt --output-dir .
$ odoc compile-impl --source-id src/main__.ml -I . main__.cmt --output-dir .
$ odoc compile -I . main__.cmt
$ odoc compile-impl --source-id main.ml -I . main.cmt --output-dir .
$ odoc compile-impl --source-id src/main.ml -I . main.cmt --output-dir .
$ odoc compile -I . main.cmt

$ odoc link -I . main.odoc
Expand All @@ -31,8 +31,9 @@ Look if all the source files are generated:
html/Main/A
html/Main/A/index.html
html/Main/index.html
html/a.ml.html
html/main.ml.html
html/src
html/src/a.ml.html
html/src/main.ml.html

$ cat html/Main/A/index.html
<!DOCTYPE html>
Expand All @@ -50,14 +51,14 @@ Look if all the source files are generated:
</nav>
<header class="odoc-preamble">
<h1>Module <code><span>Main.A</span></code>
<a href="../.././a.ml.html" class="source_link">Source</a>
<a href="../../src/a.ml.html" class="source_link">Source</a>
</h1>
</header>
<div class="odoc-content">
<div class="odoc-spec">
<div class="spec value anchored" id="val-x">
<a href="#val-x" class="anchor"></a>
<a href="../.././a.ml.html#val-x" class="source_link">Source</a>
<a href="../../src/a.ml.html#val-x" class="source_link">Source</a>
<code><span><span class="keyword">val</span> x : int</span></code>
</div>
</div>
Expand Down
25 changes: 13 additions & 12 deletions test/sources/functor.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@ Verify the behavior on functors.
$ ocamlc -c -o s.cmo s.ml -bin-annot -I .
$ ocamlc -c -o a.cmo a.ml -bin-annot -I .
$ ocamlc -c -o b.cmo b.ml -bin-annot -I .
$ odoc compile-impl --source-id s.ml -I . s.cmt --output-dir .
$ odoc compile-impl --source-id src/s.ml -I . s.cmt --output-dir .
$ odoc compile -I . s.cmt
$ odoc compile-impl --source-id a.ml -I . a.cmt --output-dir .
$ odoc compile-impl --source-id src/a.ml -I . a.cmt --output-dir .
$ odoc compile -I . a.cmt
$ odoc compile-impl --source-id b.ml -I . b.cmt --output-dir .
$ odoc compile-impl --source-id src/b.ml -I . b.cmt --output-dir .
$ odoc compile -I . b.cmt
$ odoc link -I . s.odoc
$ odoc link -I . a.odoc
Expand Down Expand Up @@ -40,23 +40,24 @@ Verify the behavior on functors.
html/S/index.html
html/S/module-type-S
html/S/module-type-S/index.html
html/a.ml.html
html/b.ml.html
html/s.ml.html
html/src
html/src/a.ml.html
html/src/b.ml.html
html/src/s.ml.html

In this test, the functor expansion contains the right link.

$ cat html/A/F/index.html | grep source_link -C 1
<h1>Module <code><span>A.F</span></code>
<a href="../.././a.ml.html#module-F" class="source_link">Source</a>
<a href="../../src/a.ml.html#module-F" class="source_link">Source</a>
</h1>
--
<a href="#type-t" class="anchor"></a>
<a href="../.././a.ml.html#module-F.type-t" class="source_link">Source
<a href="../../src/a.ml.html#module-F.type-t" class="source_link">Source
</a>
--
<a href="#val-y" class="anchor"></a>
<a href="../.././a.ml.html#module-F.val-y" class="source_link">Source
<a href="../../src/a.ml.html#module-F.val-y" class="source_link">Source
</a>

$ cat html/root/source/a.ml.html | grep L3
Expand All @@ -68,19 +69,19 @@ However, on functor results, there is a link to source in the file:
$ cat html/B/R/index.html | grep source_link -C 2
<header class="odoc-preamble">
<h1>Module <code><span>B.R</span></code>
<a href="../.././b.ml.html#module-R" class="source_link">Source</a>
<a href="../../src/b.ml.html#module-R" class="source_link">Source</a>
</h1>
</header>
--
<div class="spec type anchored" id="type-t">
<a href="#type-t" class="anchor"></a>
<a href="../.././a.ml.html#module-F.type-t" class="source_link">Source
<a href="../../src/a.ml.html#module-F.type-t" class="source_link">Source
</a>
<code><span><span class="keyword">type</span> t</span>
--
<div class="spec value anchored" id="val-y">
<a href="#val-y" class="anchor"></a>
<a href="../.././a.ml.html#module-F.val-y" class="source_link">Source
<a href="../../src/a.ml.html#module-F.val-y" class="source_link">Source
</a>
<code>

Expand Down
12 changes: 6 additions & 6 deletions test/sources/include_in_expansion.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,11 @@ Checking that source parents are kept, using include.
$ ocamlc -c -o main__A.cmo a.ml -bin-annot -I .
$ ocamlc -c main.ml -bin-annot -I .

$ odoc compile-impl --source-id b.m -I . b.cmt --output-dir .
$ odoc compile-impl --source-id src/b.m -I . b.cmt --output-dir .
$ odoc compile -I . b.cmt
$ odoc compile-impl --source-id a.ml -I . main__A.cmt --output-dir .
$ odoc compile-impl --source-id src/a.ml -I . main__A.cmt --output-dir .
$ odoc compile -I . main__A.cmt
$ odoc compile-impl --source-id main.ml -I . main.cmt --output-dir .
$ odoc compile-impl --source-id src/main.ml -I . main.cmt --output-dir .
$ odoc compile -I . main.cmt

$ odoc link -I . main.odoc
Expand All @@ -28,13 +28,13 @@ source parent of value y should be left to B.

$ grep source_link html/Main/A/index.html -C 1
<h1>Module <code><span>Main.A</span></code>
<a href="../.././a.ml.html" class="source_link">Source</a>
<a href="../../src/a.ml.html" class="source_link">Source</a>
</h1>
--
<a href="#val-y" class="anchor"></a>
<a href="../.././b.m.html#val-y" class="source_link">Source</a>
<a href="../../src/b.m.html#val-y" class="source_link">Source</a>
<code><span><span class="keyword">val</span> y : int</span></code>
--
<a href="#val-x" class="anchor"></a>
<a href="../.././a.ml.html#val-x" class="source_link">Source</a>
<a href="../../src/a.ml.html#val-x" class="source_link">Source</a>
<code><span><span class="keyword">val</span> x : int</span></code>
Loading

0 comments on commit f2014c2

Please sign in to comment.