Skip to content

Commit 0dfa632

Browse files
committed
Make tests more reproducible
1 parent d6fa38f commit 0dfa632

File tree

7 files changed

+47
-52
lines changed

7 files changed

+47
-52
lines changed

src/loader/odoc_loader.ml

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -108,7 +108,9 @@ let read_cmti ~make_root ~parent ~filename () =
108108
match cmt_info.cmt_interface_digest with
109109
| None -> raise Corrupted
110110
| Some digest as interface ->
111-
Odoc_model.Names.set_unique_ident (Digest.to_hex digest);
111+
let _ =
112+
try Odoc_model.Names.set_unique_ident (Digest.to_hex digest) with _ -> ()
113+
in
112114
let name = cmt_info.cmt_modname in
113115
let sourcefile =
114116
( cmt_info.cmt_sourcefile,
@@ -134,7 +136,8 @@ let read_cmt ~make_root ~parent ~filename () =
134136
let interface = cmt_info.cmt_interface_digest in
135137
(match cmt_info.cmt_interface_digest with
136138
| None -> raise Corrupted
137-
| Some digest -> Odoc_model.Names.set_unique_ident (Digest.to_hex digest));
139+
| Some digest ->
140+
try Odoc_model.Names.set_unique_ident (Digest.to_hex digest) with _ -> ());
138141
let imports = cmt_info.cmt_imports in
139142
match cmt_info.cmt_annots with
140143
| Packed (_, files) ->
@@ -205,7 +208,7 @@ let read_impl ~make_root ~filename ~source_id () =
205208
| None -> raise Corrupted
206209
| exception Not_found -> raise Corrupted)
207210
in
208-
Odoc_model.Names.set_unique_ident (Digest.to_hex digest);
211+
Odoc_model.Names.set_unique_ident (Odoc_model.Paths.Identifier.fullname source_id |> String.concat "-");
209212
let root =
210213
match make_root ~module_name:name ~digest with
211214
| Ok root -> root

src/odoc/bin/main.ml

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -160,6 +160,10 @@ end = struct
160160
file |> Fs.File.basename |> Fs.File.to_string
161161
|> Astring.String.is_prefix ~affix:"page-"
162162

163+
let unique_id =
164+
let doc = "For debugging use" in
165+
Arg.(value & opt (some string) None & info ~doc ~docv:"ID" ["unique-id"])
166+
163167
let output_file ~dst ~input =
164168
match dst with
165169
| Some file ->
@@ -183,8 +187,14 @@ end = struct
183187
Fs.File.(set_ext ".odoc" output)
184188

185189
let compile hidden directories resolve_fwd_refs dst package_opt
186-
parent_name_opt open_modules children input warnings_options =
190+
parent_name_opt open_modules children input warnings_options
191+
unique_id =
187192
let open Or_error in
193+
let _ =
194+
match unique_id with
195+
| Some id -> Odoc_model.Names.set_unique_ident id
196+
| None -> ()
197+
in
188198
let resolver =
189199
Resolver.create ~important_digests:(not resolve_fwd_refs) ~directories
190200
~open_modules
@@ -254,7 +264,7 @@ end = struct
254264
const handle_error
255265
$ (const compile $ hidden $ odoc_file_directories $ resolve_fwd_refs $ dst
256266
$ package_opt $ parent_opt $ open_modules $ children $ input
257-
$ warnings_options))
267+
$ warnings_options $ unique_id))
258268

259269
let info ~docs =
260270
let man =

test/sources/source.t/run.t

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -350,7 +350,7 @@ Ids generated in the source code:
350350
id="module-Yoyo.type-bli.constructor-Aa"
351351
id="module-Yoyo.type-bli.constructor-Bb"
352352
id="val-segr"
353-
id="val-{x}1/shadowed/(b7d2c9c9f02dbd7345d905f9b523044f)"
353+
id="val-{x}1/shadowed/(source-a.ml)"
354354
id="val-y"
355355
id="val-z"
356356
id="local_a_1"
@@ -367,7 +367,7 @@ Ids generated in the source code:
367367
id="class-cls"
368368
id="class-cls'"
369369
id="class-type-ct"
370-
id="val-{x}2/shadowed/(b7d2c9c9f02dbd7345d905f9b523044f)"
370+
id="val-{x}2/shadowed/(source-a.ml)"
371371
id="module-X"
372372
id="module-X.type-t"
373373
id="module-X.type-t"
@@ -382,13 +382,13 @@ Ids generated in the source code:
382382
id="module-FF2"
383383
id="module-FF2.argument-1-A.module-E"
384384
id="module-FF2.argument-2-A.module-F"
385-
id="val-{x}3/shadowed/(b7d2c9c9f02dbd7345d905f9b523044f)"
385+
id="val-{x}3/shadowed/(source-a.ml)"
386386
id="local_x_4"
387387
id="val-(*.+%)"
388388
id="val-a"
389-
id="val-{b}4/shadowed/(b7d2c9c9f02dbd7345d905f9b523044f)"
389+
id="val-{b}4/shadowed/(source-a.ml)"
390390
id="val-c"
391-
id="val-{x}5/shadowed/(b7d2c9c9f02dbd7345d905f9b523044f)"
391+
id="val-{x}5/shadowed/(source-a.ml)"
392392
id="val-b"
393393
id="val-x"
394394
id="val-list"

test/xref2/hidden_modules.t/run.t

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -137,8 +137,7 @@ There should be an expansion on `NotHidden`
137137
"`Type": [
138138
{
139139
"`Module": [
140-
{ "`Root": [ "None", "Test" ] },
141-
"NonCanonical"
140+
{ "`Root": [ "None", "Test" ] }, "NonCanonical"
142141
]
143142
},
144143
"hidden__type"

test/xref2/js_stack_overflow.t/run.t

Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,8 @@ simply finishing!
44
$ ocamlc -c import.mli -bin-annot
55
$ ocamlc -c a.mli -bin-annot
66

7-
$ odoc compile import.cmti -I .
8-
$ odoc compile a.cmti -I .
7+
$ odoc compile import.cmti -I . --unique-id IIII
8+
$ odoc compile a.cmti -I . --unique-id AAAA
99

1010
$ odoc link import.odoc -I .
1111
$ odoc link a.odoc -I .
@@ -16,15 +16,10 @@ simply finishing!
1616
(sig :
1717
include Import.S0
1818
(sig :
19-
module {Thing}1/shadowed/(3a2d2fba08409314e6d44caea0e32a6c) :
20-
sig module Config : sig end end
19+
module {Thing}1/shadowed/(IIII) : sig module Config : sig end end
2120
end)
22-
module {Thing}1/shadowed/(6dc74508933c72a27f1a6b60f24a7e4f) :
23-
sig
24-
module Config =
25-
{Thing}1/shadowed/(3a2d2fba08409314e6d44caea0e32a6c).Config
26-
(sig : end)
27-
end
21+
module {Thing}1/shadowed/(AAAA) :
22+
sig module Config = {Thing}1/shadowed/(IIII).Config (sig : end) end
2823
end)
2924
module Thing : sig end
3025

test/xref2/shadow3.t/run.t

Lines changed: 14 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -9,45 +9,33 @@ Module `C` then includes them both, causing further shadowing.
99
module type B1 = B.B1
1010
module A : sig type t = B.A.t type b = B.A.b end
1111

12-
$ odoc compile a.cmti
13-
$ odoc compile b.cmti
14-
$ odoc compile -I . c.cmti
12+
$ odoc compile a.cmti --unique-id AAAA
13+
$ odoc compile b.cmti --unique-id BBBB
14+
$ odoc compile -I . c.cmti --unique-id CCCC
1515

1616
$ odoc_print --short --show-include-expansions c.odoc
1717
include module type of struct include A end
1818
(sig :
19-
module type {B}1/shadowed/(77138ec86b57ad030798718720da7ae8) = A.B
20-
include {B}1/shadowed/(77138ec86b57ad030798718720da7ae8)
21-
(sig :
22-
module {A}1/shadowed/(7a5745e369ca21540586d74c63c97108) = A.A
23-
end)
24-
module type {B1}2/shadowed/(77138ec86b57ad030798718720da7ae8) = A.B1
25-
include {B1}2/shadowed/(77138ec86b57ad030798718720da7ae8)
26-
(sig :
27-
module {A}3/shadowed/(77138ec86b57ad030798718720da7ae8) = A.A
28-
end)
19+
module type {B}1/shadowed/(CCCC) = A.B
20+
include {B}1/shadowed/(CCCC)
21+
(sig : module {A}1/shadowed/(AAAA) = A.A end)
22+
module type {B1}2/shadowed/(CCCC) = A.B1
23+
include {B1}2/shadowed/(CCCC)
24+
(sig : module {A}3/shadowed/(CCCC) = A.A end)
2925
end)
3026
include module type of struct include B end
3127
(sig :
3228
module type B = B.B
33-
include B
34-
(sig :
35-
module {A}1/shadowed/(1ebdf715261163b09f55f3a423e7a0b0) = B.A
36-
end)
29+
include B (sig : module {A}1/shadowed/(BBBB) = B.A end)
3730
module type B1 = B.B1
38-
include B1
39-
(sig :
40-
module {A}4/shadowed/(77138ec86b57ad030798718720da7ae8) = B.A
41-
end)
31+
include B1 (sig : module {A}4/shadowed/(CCCC) = B.A end)
4232
end)
4333
module A :
4434
sig
45-
include module type of struct include {A}4/shadowed/(77138ec86b57ad030798718720da7ae8) end
35+
include module type of struct include {A}4/shadowed/(CCCC) end
4636
(sig :
47-
include module type of struct include B.{A}1/shadowed/(1ebdf715261163b09f55f3a423e7a0b0) end
48-
(sig :
49-
type t = {A}4/shadowed/(77138ec86b57ad030798718720da7ae8).t
50-
end)
37+
include module type of struct include B.{A}1/shadowed/(BBBB) end
38+
(sig : type t = {A}4/shadowed/(CCCC).t end)
5139
type b = B.A.b
5240
end)
5341
end

test/xref2/shadow5.t/run.t

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ were being incorrectly shadowed themselves - ie, the `include sig type nonrec t
2121
rewritten to be `include sig type nonrec {t}1/... = t .. end` which is incorrect.
2222

2323
$ ocamlc -bin-annot -c a.mli
24-
$ odoc compile a.cmti
24+
$ odoc compile a.cmti --unique-id AAAA
2525
$ odoc link a.odoc
2626

2727
The odocl file ought to show that, within Z, the expansion of module type Y contains a shadowed
@@ -39,7 +39,7 @@ type `t`, but in the subsequent include, the type `t` within the signature _isn'
3939
sig
4040
include Y
4141
(sig :
42-
type {t}1/shadowed/(18478640d22e31c0ec8b5408dcc5a525) = int
42+
type {t}1/shadowed/(AAAA) = int
4343
val y : int
4444
include sigtype t = t
4545
val z : tend with [t = int] (sig : val z : int end)
@@ -71,7 +71,7 @@ For comparison, another test case that didn't have the bug:
7171
end
7272

7373
$ ocamlc -bin-annot -c b.mli
74-
$ odoc compile b.cmti
74+
$ odoc compile b.cmti --unique-id BBBB
7575
$ odoc link b.odoc
7676
$ odoc_print b.odocl --short --show-include-expansions
7777
module type X = sig type t val z : t end
@@ -81,7 +81,7 @@ For comparison, another test case that didn't have the bug:
8181
sig
8282
include Y
8383
(sig :
84-
type {t}1/shadowed/(e471718aa9a93b739316d43f43b29459) = int
84+
type {t}1/shadowed/(BBBB) = int
8585
val y : int
8686
include X with [t = int] (sig : val z : int end)
8787
end)

0 commit comments

Comments
 (0)