diff --git a/Makefile b/Makefile
index 32500435cb..a85321b3e9 100644
--- a/Makefile
+++ b/Makefile
@@ -38,12 +38,7 @@ serve :
.PHONY : test
test : build
- $(DUNE) runtest $(DUNE_ARGS) src/parser/test
- $(DUNE) build $(DUNE_ARGS) @test/model/runtest --no-buffer -j 1
- $(DUNE) build $(DUNE_ARGS) @test/html/runtest --no-buffer -j 1
- $(DUNE) build $(DUNE_ARGS) @test/man/runtest --no-buffer -j 1
- $(DUNE) build $(DUNE_ARGS) @test/latex/runtest --no-buffer -j 1
- $(DUNE) build $(DUNE_ARGS) @test/xref2/runtest --no-buffer -j 1
+ $(DUNE) runtest $(DUNE_ARGS)
ODOC_RELATIVE_PATH := ../../_build/install/default/bin/
diff --git a/test/cases/ocamlary.mli b/test/cases/ocamlary.mli
deleted file mode 120000
index f8393b80e0..0000000000
--- a/test/cases/ocamlary.mli
+++ /dev/null
@@ -1 +0,0 @@
-../../src/ocamlary/ocamlary.mli
\ No newline at end of file
diff --git a/test/cases/recent_impl.ml b/test/cases/recent_impl.ml
deleted file mode 100644
index 7aa10c958d..0000000000
--- a/test/cases/recent_impl.ml
+++ /dev/null
@@ -1,29 +0,0 @@
-module Foo = struct
- module A = struct
- type t = A
- end
- module B = struct
- type t = B
- end
-end
-
-open (Foo : module type of Foo with module A := Foo.A)
-
-module B = B
-
-open Set.Make(struct type t = Foo.A.t let compare = compare end)
-
-type u = t
-
-module type S = sig
- module F: sig end -> sig type t end
- module X: sig end
- open F(X)
- val f: t
-end
-
-open Foo
-
-(* Check that regular open still works as expected *)
-module B' = B
-
diff --git a/test/cases/.ocamlformat b/test/generators/cases_post408/cases/.ocamlformat
similarity index 100%
rename from test/cases/.ocamlformat
rename to test/generators/cases_post408/cases/.ocamlformat
diff --git a/test/cases/bugs_post_406.mli b/test/generators/cases_post408/cases/bugs_post_406.mli
similarity index 100%
rename from test/cases/bugs_post_406.mli
rename to test/generators/cases_post408/cases/bugs_post_406.mli
diff --git a/test/cases/labels.mli b/test/generators/cases_post408/cases/labels.mli
similarity index 89%
rename from test/cases/labels.mli
rename to test/generators/cases_post408/cases/labels.mli
index 5b361ca20e..f180a63deb 100644
--- a/test/cases/labels.mli
+++ b/test/generators/cases_post408/cases/labels.mli
@@ -2,44 +2,44 @@
(** {1:L2 Attached to nothing} *)
-(** {1:L3 Attached to module} *)
module A : sig end
+(** {1:L3 Attached to module} *)
-(** {1:L4 Attached to type} *)
type t
+(** {1:L4 Attached to type} *)
-(** {1:L5 Attached to value} *)
val f : t
+(** {1:L5 Attached to value} *)
-(** {1:L5bis Attached to external} *)
external e : unit -> t = "t"
+(** {1:L5bis Attached to external} *)
-(** {1:L6 Attached to module type} *)
module type S = sig end
+(** {1:L6 Attached to module type} *)
-(** {1:L6 Attached to class} *)
class c : object end
+(** {1:L6 Attached to class} *)
-(** {1:L7 Attached to class type} *)
class type cs = object end
+(** {1:L7 Attached to class type} *)
-(** {1:L8 Attached to exception} *)
exception E
+(** {1:L8 Attached to exception} *)
type x = ..
(** {1:L9 Attached to extension} *)
type x += X
-(** {1:L10 Attached to module subst} *)
module S := A
+(** {1:L10 Attached to module subst} *)
-(** {1:L11 Attached to type subst} *)
type s := t
+(** {1:L11 Attached to type subst} *)
-type u = A' (** {1:L12 Attached to constructor} *)
+type u = A' (** {1:L12 Attached to constructor} *)
-type v = { f : t (** {1:L13 Attached to field} *) }
+type v = { f : t (** {1:L13 Attached to field} *) }
(** Testing that labels can be referenced
- {!L1}
diff --git a/test/cases/recent.mli b/test/generators/cases_post408/cases/recent.mli
similarity index 55%
rename from test/cases/recent.mli
rename to test/generators/cases_post408/cases/recent.mli
index a6ceb09654..773504acf8 100644
--- a/test/cases/recent.mli
+++ b/test/generators/cases_post408/cases/recent.mli
@@ -4,37 +4,34 @@
module type S = sig end
-module type S1 = S -> S
+module type S1 = functor (_ : S) -> S
type variant =
| A
| B of int
- | C (** foo *)
- | D (** {e bar} *)
- | E of {a : int}
+ | C (** foo *)
+ | D (** {e bar} *)
+ | E of { a : int }
type _ gadt =
| A : int gadt
- | B : int -> string gadt (** foo *)
- | C : {a : int} -> unit gadt
+ | B : int -> string gadt (** foo *)
+ | C : { a : int } -> unit gadt
-type polymorphic_variant = [
- | `A
- | `B of int
- | `C (** foo *)
- | `D (** bar *)
-]
+type polymorphic_variant = [ `A | `B of int | `C (** foo *) | `D (** bar *) ]
type empty_variant = |
type nonrec nonrec_ = int
-
(* Conjunctive types: dune compilation scheme exposes a bug in old
versions of the compiler *)
-type empty_conj= X: [< `X of & 'a & int * float ] -> empty_conj
-type conj = X: [< `X of int & [< `B of int & float ] ] -> conj
-val empty_conj: [< `X of & 'a & int * float ]
+type empty_conj = X : [< `X of & 'a & int * float ] -> empty_conj
+
+type conj = X : [< `X of int & [< `B of int & float ] ] -> conj
+
+val empty_conj : [< `X of & 'a & int * float ]
+
val conj : [< `X of int & [< `B of int & float ] ]
module Z : sig
@@ -47,12 +44,17 @@ end
module X : sig
module L := Z.Y
+
type t = int L.X.t
+
type u := int
+
type v = u L.X.t
end
-module type PolyS =
- sig type a = [ `A ] type t = [ a | `B ] end with type a := [ `A ]
-
+module type PolyS = sig
+ type a = [ `A ]
+ type t = [ a | `B ]
+end
+with type a := [ `A ]
diff --git a/test/generators/cases_post408/cases/recent_impl.ml b/test/generators/cases_post408/cases/recent_impl.ml
new file mode 100644
index 0000000000..fce38772f0
--- /dev/null
+++ b/test/generators/cases_post408/cases/recent_impl.ml
@@ -0,0 +1,38 @@
+module Foo = struct
+ module A = struct
+ type t = A
+ end
+
+ module B = struct
+ type t = B
+ end
+end
+
+open (Foo : module type of Foo with module A := Foo.A)
+
+module B = B
+
+open Set.Make (struct
+ type t = Foo.A.t
+
+ let compare = compare
+end)
+
+type u = t
+
+module type S = sig
+ module F (_ : sig end) : sig
+ type t
+ end
+
+ module X : sig end
+
+ open F(X)
+
+ val f : t
+end
+
+open Foo
+
+(* Check that regular open still works as expected *)
+module B' = B
diff --git a/test/generators/cases_post408/dune b/test/generators/cases_post408/dune
new file mode 100644
index 0000000000..212e15cda6
--- /dev/null
+++ b/test/generators/cases_post408/dune
@@ -0,0 +1,20 @@
+(include link.dune.inc)
+
+(rule
+ (deps
+ (glob_files cases/*))
+ (enabled_if
+ (>= %{ocaml_version} 4.08))
+ (action
+ (with-stdout-to
+ link.dune.inc.gen
+ (pipe-stdout
+ (run gen_link/gen_link.exe)
+ (run dune format-dune-file)))))
+
+(rule
+ (enabled_if
+ (>= %{ocaml_version} 4.08))
+ (alias runtest)
+ (action
+ (diff link.dune.inc link.dune.inc.gen)))
diff --git a/test/generators/cases_post408/gen_link/dune b/test/generators/cases_post408/gen_link/dune
new file mode 100644
index 0000000000..7579f2ecf2
--- /dev/null
+++ b/test/generators/cases_post408/gen_link/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_link)
+ (libraries gen_link_lib)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_post408/gen_link/gen_link.ml b/test/generators/cases_post408/gen_link/gen_link.ml
new file mode 100644
index 0000000000..cdec4729d3
--- /dev/null
+++ b/test/generators/cases_post408/gen_link/gen_link.ml
@@ -0,0 +1,9 @@
+let () =
+ let paths =
+ Gen_link_lib.read_file_from_dir (Fpath.filename Gen_link_lib.cases)
+ in
+ let paths =
+ List.filter (fun p -> not (Gen_link_lib.is_dot_ocamlformat p)) paths
+ in
+ let stanzas = Gen_link_lib.gen_rule paths "4.08" in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_post408/html/Bugs_post_406.class-let_open'.index.html b/test/generators/cases_post408/html/Bugs_post_406.class-let_open'.index.html
new file mode 100644
index 0000000000..7e3ed2b285
--- /dev/null
+++ b/test/generators/cases_post408/html/Bugs_post_406.class-let_open'.index.html
@@ -0,0 +1,19 @@
+
+
+
let_open' (test.Bugs_post_406.let_open')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Bugs_post_406 » let_open'
+
+
+ Class Bugs_post_406.let_open'
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Bugs_post_406.class-type-let_open.index.html b/test/generators/cases_post408/html/Bugs_post_406.class-type-let_open.index.html
new file mode 100644
index 0000000000..081e6ce386
--- /dev/null
+++ b/test/generators/cases_post408/html/Bugs_post_406.class-type-let_open.index.html
@@ -0,0 +1,19 @@
+
+
+ let_open (test.Bugs_post_406.let_open)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Bugs_post_406 » let_open
+
+
+ Class type Bugs_post_406.let_open
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Bugs_post_406.index.html b/test/generators/cases_post408/html/Bugs_post_406.index.html
new file mode 100644
index 0000000000..3719f6c912
--- /dev/null
+++ b/test/generators/cases_post408/html/Bugs_post_406.index.html
@@ -0,0 +1,48 @@
+
+
+ Bugs_post_406 (test.Bugs_post_406)
+
+
+
+
+
+
+
+ Up –
+ test » Bugs_post_406
+
+
+
+
+
+
+
+ class
+ type
+
+ let_open
+ = object ...
+ end
+
+
+
+
+
+
+
+
class
+ let_open'
+ : object ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Labels.A.index.html b/test/generators/cases_post408/html/Labels.A.index.html
new file mode 100644
index 0000000000..cd3086c154
--- /dev/null
+++ b/test/generators/cases_post408/html/Labels.A.index.html
@@ -0,0 +1,25 @@
+
+
+ A (test.Labels.A)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Labels » A
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Labels.class-c.index.html b/test/generators/cases_post408/html/Labels.class-c.index.html
new file mode 100644
index 0000000000..e5a3c5440e
--- /dev/null
+++ b/test/generators/cases_post408/html/Labels.class-c.index.html
@@ -0,0 +1,24 @@
+
+
+ c (test.Labels.c)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Labels » c
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Labels.class-type-cs.index.html b/test/generators/cases_post408/html/Labels.class-type-cs.index.html
new file mode 100644
index 0000000000..01c4306d80
--- /dev/null
+++ b/test/generators/cases_post408/html/Labels.class-type-cs.index.html
@@ -0,0 +1,25 @@
+
+
+ cs (test.Labels.cs)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Labels » cs
+
+
+
+
+
+
+
Attached to class type
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Labels.index.html b/test/generators/cases_post408/html/Labels.index.html
new file mode 100644
index 0000000000..124217ff85
--- /dev/null
+++ b/test/generators/cases_post408/html/Labels.index.html
@@ -0,0 +1,202 @@
+
+
+ Labels (test.Labels)
+
+
+
+
+
+
+
+ Up –
+ test » Labels
+
+
+
+
+
+
+
Attached to unit
+
Attached to nothing
+
+
+
+
module
+ A
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
+
+ val e :
+ unit ->
+ t
+
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
class
+ c
+ : object ...
+ end
+
+
+
+
+
+
+
+
+ class
+ type
+ cs
+ = object ...
+ end
+
+
+
+
+
+
+
+
+
+
+
+ module S :=
+ A
+
+
+
+
+
+
+
+
+
type u =
+
+
+
+
+
+ | A'
+
+
+
+ Attached to constructor
+
+
+
+
+
+
+
+
+
type v =
+ {
+
+
+
+
+ f : t ;
+
+
+ Attached to field
+
+
+
}
+
+
Testing that labels can be referenced
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Labels.module-type-S.index.html b/test/generators/cases_post408/html/Labels.module-type-S.index.html
new file mode 100644
index 0000000000..a310cc87a2
--- /dev/null
+++ b/test/generators/cases_post408/html/Labels.module-type-S.index.html
@@ -0,0 +1,25 @@
+
+
+ S (test.Labels.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Labels » S
+
+
+
+
+
+
+
Attached to module type
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.X.index.html b/test/generators/cases_post408/html/Recent.X.index.html
new file mode 100644
index 0000000000..8ab96fe918
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.X.index.html
@@ -0,0 +1,61 @@
+
+
+ X (test.Recent.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent » X
+
+
+
+
+
+
+
+ module L :=
+ Z.Y
+
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.Z.Y.X.index.html b/test/generators/cases_post408/html/Recent.Z.Y.X.index.html
new file mode 100644
index 0000000000..0a7350116b
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.Z.Y.X.index.html
@@ -0,0 +1,29 @@
+
+
+ X (test.Recent.Z.Y.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent »
+ Z » Y
+ » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.Z.Y.index.html b/test/generators/cases_post408/html/Recent.Z.Y.index.html
new file mode 100644
index 0000000000..3d9b323258
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.Z.Y.index.html
@@ -0,0 +1,32 @@
+
+
+ Y (test.Recent.Z.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent »
+ Z » Y
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.Z.index.html b/test/generators/cases_post408/html/Recent.Z.index.html
new file mode 100644
index 0000000000..dc40eb2bbe
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.Z.index.html
@@ -0,0 +1,32 @@
+
+
+ Z (test.Recent.Z)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent » Z
+
+
+
+
+
+
+
module
+ Y
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.index.html b/test/generators/cases_post408/html/Recent.index.html
new file mode 100644
index 0000000000..f9903b7b42
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.index.html
@@ -0,0 +1,340 @@
+
+
+ Recent (test.Recent)
+
+
+
+
+
+
+
+ Up –
+ test » Recent
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ S1
+ = functor
+ (_
+ : S )
+ ->
+ S
+
+
+
+
+
+
+
+
type variant
+ =
+
+
+
+
+
+ | A
+
+
+
+
+
+
+ |
+ B
+ of int
+
+
+
+
+
+
+
+ | C
+
+
+ foo
+
+
+
+
+
+
+ | D
+
+
+
+ bar
+
+
+
+
+
+ |
+ E
+ of
+ {
+
+ }
+
+
+
+
+
+
+
+
+
type _ gadt
+ =
+
+
+
+
+
+ |
+ A :
+ int gadt
+
+
+
+
+
+
+
+ |
+ B : int
+ ->
+ string gadt
+
+
+
+ foo
+
+
+
+
+
+
+ |
+ C : {
+
+
+ }
+ ->
+ unit gadt
+
+
+
+
+
+
+
+
+
+
+
type polymorphic_variant
+ = [
+
+
+
+
+
+ |
`A
+
+
+
+
+
+ |
+ `B of int
+
+
+
+
+
+ |
`C
+
+ foo
+
+
+
+
+
+
+ |
`D
+
+ bar
+
+
+
+
]
+
+
+
+
+
+
type empty_variant
+ = |
+
+
+
+
+
+
+
+ type
+ nonrec nonrec_
+ = int
+
+
+
+
+
+
+
type empty_conj
+ =
+
+
+
+
+
+ |
+ X :
+ [<
+ `X of & 'a & int
+ * float
+ ]
+ ->
+ empty_conj
+
+
+
+
+
+
+
+
+
+
+
type conj
+ =
+
+
+
+
+
+ |
+ X :
+ [<
+ `X of int &
+ [< `B of int & float ]
+ ]
+ ->
+ conj
+
+
+
+
+
+
+
+
+
+
+
+ val empty_conj :
+ [<
+ `X of & 'a & int * float
+ ]
+
+
+
+
+
+
+
+
+
+ val conj :
+ [<
+ `X of int &
+ [< `B of int & float ]
+ ]
+
+
+
+
+
+
+
+
+
module
+ Z
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ PolyS
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.module-type-PolyS.index.html b/test/generators/cases_post408/html/Recent.module-type-PolyS.index.html
new file mode 100644
index 0000000000..462ed05678
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.module-type-PolyS.index.html
@@ -0,0 +1,41 @@
+
+
+ PolyS (test.Recent.PolyS)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent » PolyS
+
+
+ Module type Recent.PolyS
+
+
+
+
+
+
type t =
+ [
+
+
+
+
+ |
`A
+
+
+
+
+ |
`B
+
+
+
]
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.module-type-S.index.html b/test/generators/cases_post408/html/Recent.module-type-S.index.html
new file mode 100644
index 0000000000..167f0d3a2e
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.module-type-S.index.html
@@ -0,0 +1,19 @@
+
+
+ S (test.Recent.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent » S
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.module-type-S1.argument-1-_.index.html b/test/generators/cases_post408/html/Recent.module-type-S1.argument-1-_.index.html
new file mode 100644
index 0000000000..aadedfc888
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.module-type-S1.argument-1-_.index.html
@@ -0,0 +1,20 @@
+
+
+ _ (test.Recent.S1.1-_)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent »
+ S1 » 1-_
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent.module-type-S1.index.html b/test/generators/cases_post408/html/Recent.module-type-S1.index.html
new file mode 100644
index 0000000000..ec8081cc6d
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent.module-type-S1.index.html
@@ -0,0 +1,38 @@
+
+
+ S1 (test.Recent.S1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent » S1
+
+
+ Module type Recent.S1
+
+
+
+
+
+
Parameters
+
+
+
Signature
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.B.index.html b/test/generators/cases_post408/html/Recent_impl.B.index.html
new file mode 100644
index 0000000000..e36576feb5
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.B.index.html
@@ -0,0 +1,37 @@
+
+
+ B (test.Recent_impl.B)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl » B
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.Foo.A.index.html b/test/generators/cases_post408/html/Recent_impl.Foo.A.index.html
new file mode 100644
index 0000000000..fc68d4d307
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.Foo.A.index.html
@@ -0,0 +1,38 @@
+
+
+ A (test.Recent_impl.Foo.A)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl »
+ Foo » A
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.Foo.B.index.html b/test/generators/cases_post408/html/Recent_impl.Foo.B.index.html
new file mode 100644
index 0000000000..8e7fbd70cf
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.Foo.B.index.html
@@ -0,0 +1,38 @@
+
+
+ B (test.Recent_impl.Foo.B)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl »
+ Foo » B
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.Foo.index.html b/test/generators/cases_post408/html/Recent_impl.Foo.index.html
new file mode 100644
index 0000000000..22c862c541
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.Foo.index.html
@@ -0,0 +1,43 @@
+
+
+ Foo (test.Recent_impl.Foo)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl » Foo
+
+
+ Module Recent_impl.Foo
+
+
+
+
+
+
module
+ A
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ B
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.index.html b/test/generators/cases_post408/html/Recent_impl.index.html
new file mode 100644
index 0000000000..c169694af9
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.index.html
@@ -0,0 +1,69 @@
+
+
+ Recent_impl (test.Recent_impl)
+
+
+
+
+
+
+
+ Up –
+ test » Recent_impl
+
+
+
+
+
+
+
module
+ Foo
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ B
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
module B'
+ = Foo.B
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.module-type-S.F.argument-1-_.index.html b/test/generators/cases_post408/html/Recent_impl.module-type-S.F.argument-1-_.index.html
new file mode 100644
index 0000000000..a4a8a1d9ea
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.module-type-S.F.argument-1-_.index.html
@@ -0,0 +1,21 @@
+
+
+ _ (test.Recent_impl.S.F.1-_)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl »
+ S » F
+ » 1-_
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.module-type-S.F.index.html b/test/generators/cases_post408/html/Recent_impl.module-type-S.F.index.html
new file mode 100644
index 0000000000..8d91b22db3
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.module-type-S.F.index.html
@@ -0,0 +1,46 @@
+
+
+ F (test.Recent_impl.S.F)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl »
+ S » F
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ _
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.module-type-S.X.index.html b/test/generators/cases_post408/html/Recent_impl.module-type-S.X.index.html
new file mode 100644
index 0000000000..e82f6da7f8
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.module-type-S.X.index.html
@@ -0,0 +1,19 @@
+
+
+ X (test.Recent_impl.S.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl »
+ S » X
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/Recent_impl.module-type-S.index.html b/test/generators/cases_post408/html/Recent_impl.module-type-S.index.html
new file mode 100644
index 0000000000..6a7f41f56c
--- /dev/null
+++ b/test/generators/cases_post408/html/Recent_impl.module-type-S.index.html
@@ -0,0 +1,55 @@
+
+
+ S (test.Recent_impl.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Recent_impl » S
+
+
+ Module type Recent_impl.S
+
+
+
+
+
+
module
+ F
+ (_ :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_post408/html/dune b/test/generators/cases_post408/html/dune
new file mode 100644
index 0000000000..1900258c3c
--- /dev/null
+++ b/test/generators/cases_post408/html/dune
@@ -0,0 +1 @@
+(include html.dune.inc)
diff --git a/test/generators/cases_post408/html/gen_html/dune b/test/generators/cases_post408/html/gen_html/dune
new file mode 100644
index 0000000000..7bf6d5d0a0
--- /dev/null
+++ b/test/generators/cases_post408/html/gen_html/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_html)
+ (libraries html_t_rule)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_post408/html/gen_html/gen_html.ml b/test/generators/cases_post408/html/gen_html/gen_html.ml
new file mode 100644
index 0000000000..6c4bdc9427
--- /dev/null
+++ b/test/generators/cases_post408/html/gen_html/gen_html.ml
@@ -0,0 +1,6 @@
+let () =
+ let stanzas =
+ Gen_backend.gen_backend_rules "html" Html_t_rule.html_target_rule
+ Gen_backend.files "4.08"
+ in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_post408/html/html.dune.inc b/test/generators/cases_post408/html/html.dune.inc
new file mode 100644
index 0000000000..b995318fa8
--- /dev/null
+++ b/test/generators/cases_post408/html/html.dune.inc
@@ -0,0 +1,333 @@
+(rule
+ (action
+ (progn
+ (run
+ odoc
+ html-generate
+ --indent
+ -o
+ html.gen
+ %{dep:../bugs_post_406.odocl})
+ (with-stdout-to
+ Bugs_post_406.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Bugs_post_406/index.html'")))
+ (with-stdout-to
+ Bugs_post_406.class-type-let_open.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Bugs_post_406/class-type-let_open/index.html'")))
+ (with-stdout-to
+ Bugs_post_406.class-let_open'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Bugs_post_406/class-let_open'\\''/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_post_406.index.html Bugs_post_406.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Bugs_post_406.class-type-let_open.index.html
+ Bugs_post_406.class-type-let_open.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Bugs_post_406.class-let_open'.index.html
+ Bugs_post_406.class-let_open'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../labels.odocl})
+ (with-stdout-to
+ Labels.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Labels/index.html'")))
+ (with-stdout-to
+ Labels.A.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Labels/A/index.html'")))
+ (with-stdout-to
+ Labels.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Labels/module-type-S/index.html'")))
+ (with-stdout-to
+ Labels.class-c.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Labels/class-c/index.html'")))
+ (with-stdout-to
+ Labels.class-type-cs.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Labels/class-type-cs/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.index.html Labels.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.A.index.html Labels.A.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.module-type-S.index.html Labels.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.class-c.index.html Labels.class-c.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.class-type-cs.index.html Labels.class-type-cs.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../recent.odocl})
+ (with-stdout-to
+ Recent.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/index.html'")))
+ (with-stdout-to
+ Recent.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/module-type-S/index.html'")))
+ (with-stdout-to
+ Recent.module-type-S1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/module-type-S1/index.html'")))
+ (with-stdout-to
+ Recent.module-type-S1.argument-1-_.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Recent/module-type-S1/argument-1-_/index.html'")))
+ (with-stdout-to
+ Recent.Z.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/Z/index.html'")))
+ (with-stdout-to
+ Recent.Z.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/Z/Y/index.html'")))
+ (with-stdout-to
+ Recent.Z.Y.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/Z/Y/X/index.html'")))
+ (with-stdout-to
+ Recent.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/X/index.html'")))
+ (with-stdout-to
+ Recent.module-type-PolyS.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent/module-type-PolyS/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.index.html Recent.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.module-type-S.index.html Recent.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent.module-type-S1.index.html
+ Recent.module-type-S1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent.module-type-S1.argument-1-_.index.html
+ Recent.module-type-S1.argument-1-_.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.Z.index.html Recent.Z.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.Z.Y.index.html Recent.Z.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.Z.Y.X.index.html Recent.Z.Y.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.X.index.html Recent.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent.module-type-PolyS.index.html
+ Recent.module-type-PolyS.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../recent_impl.odocl})
+ (with-stdout-to
+ Recent_impl.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/index.html'")))
+ (with-stdout-to
+ Recent_impl.Foo.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/Foo/index.html'")))
+ (with-stdout-to
+ Recent_impl.Foo.A.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/Foo/A/index.html'")))
+ (with-stdout-to
+ Recent_impl.Foo.B.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/Foo/B/index.html'")))
+ (with-stdout-to
+ Recent_impl.B.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/B/index.html'")))
+ (with-stdout-to
+ Recent_impl.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/module-type-S/index.html'")))
+ (with-stdout-to
+ Recent_impl.module-type-S.F.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/module-type-S/F/index.html'")))
+ (with-stdout-to
+ Recent_impl.module-type-S.F.argument-1-_.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Recent_impl/module-type-S/F/argument-1-_/index.html'")))
+ (with-stdout-to
+ Recent_impl.module-type-S.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Recent_impl/module-type-S/X/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.index.html Recent_impl.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.Foo.index.html Recent_impl.Foo.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.Foo.A.index.html Recent_impl.Foo.A.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.Foo.B.index.html Recent_impl.Foo.B.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.B.index.html Recent_impl.B.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent_impl.module-type-S.index.html
+ Recent_impl.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent_impl.module-type-S.F.index.html
+ Recent_impl.module-type-S.F.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent_impl.module-type-S.F.argument-1-_.index.html
+ Recent_impl.module-type-S.F.argument-1-_.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Recent_impl.module-type-S.X.index.html
+ Recent_impl.module-type-S.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
diff --git a/test/generators/cases_post408/latex/Bugs_post_406.let_open'.tex b/test/generators/cases_post408/latex/Bugs_post_406.let_open'.tex
new file mode 100644
index 0000000000..dda7495991
--- /dev/null
+++ b/test/generators/cases_post408/latex/Bugs_post_406.let_open'.tex
@@ -0,0 +1,3 @@
+\section{Class \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406.\allowbreak{}let\_\allowbreak{}open'}}\label{container-page-test-module-Bugs+u+post+u+406-class-let+u+open'}%
+
+
diff --git a/test/generators/cases_post408/latex/Bugs_post_406.tex b/test/generators/cases_post408/latex/Bugs_post_406.tex
new file mode 100644
index 0000000000..012f563229
--- /dev/null
+++ b/test/generators/cases_post408/latex/Bugs_post_406.tex
@@ -0,0 +1,8 @@
+\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406}}\label{container-page-test-module-Bugs+u+post+u+406}%
+Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06
+
+\label{container-page-test-module-Bugs+u+post+u+406-class-type-let+u+open}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Bugs+u+post+u+406-class-type-let+u+open]{\ocamlinlinecode{let\_\allowbreak{}open}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Bugs+u+post+u+406-class-let+u+open'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Bugs+u+post+u+406-class-let+u+open']{\ocamlinlinecode{let\_\allowbreak{}open'}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+
+\input{test/Bugs_post_406.let_open'.tex}
diff --git a/test/generators/cases_post408/latex/Labels.c.tex b/test/generators/cases_post408/latex/Labels.c.tex
new file mode 100644
index 0000000000..5e73a39ca3
--- /dev/null
+++ b/test/generators/cases_post408/latex/Labels.c.tex
@@ -0,0 +1,4 @@
+\section{Class \ocamlinlinecode{Labels.\allowbreak{}c}}\label{container-page-test-module-Labels-class-c}%
+\subsection{Attached to class\label{L6}}%
+
+
diff --git a/test/generators/cases_post408/latex/Labels.tex b/test/generators/cases_post408/latex/Labels.tex
new file mode 100644
index 0000000000..de97645a2e
--- /dev/null
+++ b/test/generators/cases_post408/latex/Labels.tex
@@ -0,0 +1,58 @@
+\section{Module \ocamlinlinecode{Labels}}\label{container-page-test-module-Labels}%
+\subsection{Attached to unit\label{L1}}%
+\subsection{Attached to nothing\label{L2}}%
+\label{container-page-test-module-Labels-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Labels-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module\label{L3}}%
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Labels-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Attached to type\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[container-page-test-module-Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to value\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : unit \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to external\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Labels-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module type\label{L6}}%
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Labels-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Labels-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L7}}%
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Labels-exception-E}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{E}}\begin{ocamlindent}Attached to exception\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-type-x}\ocamlcodefragment{\ocamltag{keyword}{type} x = .\allowbreak{}.\allowbreak{}}\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Labels-type-x]{\ocamlinlinecode{x}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{X}}\label{container-page-test-module-Labels-extension-X}\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}Attached to extension\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-module-S}\ocamlcodefragment{\ocamltag{keyword}{module} S := \hyperref[container-page-test-module-Labels-module-A]{\ocamlinlinecode{A}}}\begin{ocamlindent}Attached to module subst\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s := \hyperref[container-page-test-module-Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to type subst\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Labels-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A'}}\label{container-page-test-module-Labels-type-u.A'}& Attached to constructor\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Labels-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \{}\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{f : \hyperref[container-page-test-module-Labels-type-t]{\ocamlinlinecode{t}};\allowbreak{}}\label{container-page-test-module-Labels-type-v.f}& Attached to field\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\\
+Testing that labels can be referenced
+
+\begin{itemize}\item{\hyperref[container-page-test-module-Labels-L1]{\ocamlinlinecode{Attached to unit}[p\pageref*{container-page-test-module-Labels-L1}]}}%
+\item{\hyperref[container-page-test-module-Labels-L2]{\ocamlinlinecode{Attached to nothing}[p\pageref*{container-page-test-module-Labels-L2}]}}%
+\item{\hyperref[container-page-test-module-Labels-L3]{\ocamlinlinecode{Attached to module}[p\pageref*{container-page-test-module-Labels-L3}]}}%
+\item{\hyperref[container-page-test-module-Labels-L4]{\ocamlinlinecode{Attached to type}[p\pageref*{container-page-test-module-Labels-L4}]}}%
+\item{\hyperref[container-page-test-module-Labels-L5]{\ocamlinlinecode{Attached to value}[p\pageref*{container-page-test-module-Labels-L5}]}}%
+\item{\hyperref[container-page-test-module-Labels-L6]{\ocamlinlinecode{Attached to class}[p\pageref*{container-page-test-module-Labels-L6}]}}%
+\item{\hyperref[container-page-test-module-Labels-L7]{\ocamlinlinecode{Attached to class type}[p\pageref*{container-page-test-module-Labels-L7}]}}%
+\item{\hyperref[container-page-test-module-Labels-L8]{\ocamlinlinecode{Attached to exception}[p\pageref*{container-page-test-module-Labels-L8}]}}%
+\item{\hyperref[container-page-test-module-Labels-L9]{\ocamlinlinecode{Attached to extension}[p\pageref*{container-page-test-module-Labels-L9}]}}%
+\item{\hyperref[container-page-test-module-Labels-L10]{\ocamlinlinecode{Attached to module subst}[p\pageref*{container-page-test-module-Labels-L10}]}}%
+\item{\hyperref[container-page-test-module-Labels-L11]{\ocamlinlinecode{Attached to type subst}[p\pageref*{container-page-test-module-Labels-L11}]}}%
+\item{\hyperref[container-page-test-module-Labels-L12]{\ocamlinlinecode{Attached to constructor}[p\pageref*{container-page-test-module-Labels-L12}]}}%
+\item{\hyperref[container-page-test-module-Labels-L13]{\ocamlinlinecode{Attached to field}[p\pageref*{container-page-test-module-Labels-L13}]}}\end{itemize}%
+
+\input{test/Labels.c.tex}
diff --git a/test/generators/cases_post408/latex/Recent.tex b/test/generators/cases_post408/latex/Recent.tex
new file mode 100644
index 0000000000..3efc02749d
--- /dev/null
+++ b/test/generators/cases_post408/latex/Recent.tex
@@ -0,0 +1,78 @@
+\section{Module \ocamlinlinecode{Recent}}\label{container-page-test-module-Recent}%
+\label{container-page-test-module-Recent-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Recent-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Recent-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Recent-module-type-S1-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent-module-type-S1-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsubsection{Signature\label{signature}}%
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test-module-Recent-type-variant.A}%
+\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{container-page-test-module-Recent-type-variant.B}%
+\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{container-page-test-module-Recent-type-variant.C}%
+\begin{ocamlindent}foo\end{ocamlindent}%
+\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{container-page-test-module-Recent-type-variant.D}%
+\begin{ocamlindent}\emph{bar}\end{ocamlindent}%
+\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test-module-Recent-type-variant.a}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\label{container-page-test-module-Recent-type-variant.E}%
+\begin{ocamlindent}\end{ocamlindent}%
+\end{ocamlindent}%
+\label{container-page-test-module-Recent-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[container-page-test-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test-module-Recent-type-gadt.A}%
+\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[container-page-test-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test-module-Recent-type-gadt.B}%
+\begin{ocamlindent}foo\end{ocamlindent}%
+\ocamlcodefragment{| \ocamltag{constructor}{C} : \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test-module-Recent-type-gadt.a}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[container-page-test-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test-module-Recent-type-gadt.C}%
+\begin{ocamlindent}\end{ocamlindent}%
+\end{ocamlindent}%
+\label{container-page-test-module-Recent-type-polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test-module-Recent-type-polymorphic+u+variant.A}& \\
+\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} int}\label{container-page-test-module-Recent-type-polymorphic+u+variant.B}& \\
+\ocamlinlinecode{| }\ocamlinlinecode{`C}\label{container-page-test-module-Recent-type-polymorphic+u+variant.C}& foo\\
+\ocamlinlinecode{| }\ocamlinlinecode{`D}\label{container-page-test-module-Recent-type-polymorphic+u+variant.D}& bar\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Recent-type-empty+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}variant = |}\\
+\label{container-page-test-module-Recent-type-nonrec+u+}\ocamlcodefragment{\ocamltag{keyword}{type} \ocamltag{keyword}{nonrec} nonrec\_\allowbreak{} = int}\\
+\label{container-page-test-module-Recent-type-empty+u+conj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}conj = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of \& \ocamltag{type-var}{'a} \& int * float ] \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Recent-type-empty+u+conj]{\ocamlinlinecode{empty\_\allowbreak{}conj}}}\label{container-page-test-module-Recent-type-empty+u+conj.X}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Recent-type-conj}\ocamlcodefragment{\ocamltag{keyword}{type} conj = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of int \& [< `B of int \& float ] ] \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Recent-type-conj]{\ocamlinlinecode{conj}}}\label{container-page-test-module-Recent-type-conj.X}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Recent-val-empty+u+conj}\ocamlcodefragment{\ocamltag{keyword}{val} empty\_\allowbreak{}conj : [< `X of \& \ocamltag{type-var}{'a} \& int * float ]}\\
+\label{container-page-test-module-Recent-val-conj}\ocamlcodefragment{\ocamltag{keyword}{val} conj : [< `X of int \& [< `B of int \& float ] ]}\\
+\label{container-page-test-module-Recent-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent-module-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent-module-Z-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent-module-Z-module-Y-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent-module-Z-module-Y-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent-module-Z-module-Y-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} 'a t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent-module-X-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L := \hyperref[container-page-test-module-Recent-module-Z-module-Y]{\ocamlinlinecode{Z.\allowbreak{}Y}}}\\
+\label{container-page-test-module-Recent-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int \hyperref[container-page-test-module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\
+\label{container-page-test-module-Recent-module-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u := int}\\
+\label{container-page-test-module-Recent-module-X-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \hyperref[container-page-test-module-Recent-module-X-type-u]{\ocamlinlinecode{u}} \hyperref[container-page-test-module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent-module-type-PolyS}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Recent-module-type-PolyS]{\ocamlinlinecode{PolyS}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent-module-type-PolyS-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test-module-Recent-module-type-PolyS-type-t.A}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`B}\label{container-page-test-module-Recent-module-type-PolyS-type-t.B}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+
+
diff --git a/test/generators/cases_post408/latex/Recent_impl.B.tex b/test/generators/cases_post408/latex/Recent_impl.B.tex
new file mode 100644
index 0000000000..1ee8741511
--- /dev/null
+++ b/test/generators/cases_post408/latex/Recent_impl.B.tex
@@ -0,0 +1,7 @@
+\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl.\allowbreak{}B}}\label{container-page-test-module-Recent+u+impl-module-B}%
+\label{container-page-test-module-Recent+u+impl-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{container-page-test-module-Recent+u+impl-module-B-type-t.B}\\
+\end{ocamltabular}%
+\\
+
+
diff --git a/test/generators/cases_post408/latex/Recent_impl.tex b/test/generators/cases_post408/latex/Recent_impl.tex
new file mode 100644
index 0000000000..cb58359787
--- /dev/null
+++ b/test/generators/cases_post408/latex/Recent_impl.tex
@@ -0,0 +1,32 @@
+\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl}}\label{container-page-test-module-Recent+u+impl}%
+\label{container-page-test-module-Recent+u+impl-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent+u+impl-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent+u+impl-module-Foo-module-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test-module-Recent+u+impl-module-Foo-module-A-type-t.A}\\
+\end{ocamltabular}%
+\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent+u+impl-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent+u+impl-module-Foo-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{container-page-test-module-Recent+u+impl-module-Foo-module-B-type-t.B}\\
+\end{ocamltabular}%
+\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent+u+impl-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent+u+impl-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Recent+u+impl-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Recent+u+impl-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Recent+u+impl-module-type-S-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-type-S-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsubsection{Signature\label{signature}}%
+\label{container-page-test-module-Recent+u+impl-module-type-S-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent+u+impl-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Recent+u+impl-module-type-S-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent+u+impl-module-type-S-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[container-page-test-module-Recent+u+impl-module-type-S-module-F-type-t]{\ocamlinlinecode{F(X).\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Recent+u+impl-module-B'}\ocamlcodefragment{\ocamltag{keyword}{module} B' = \hyperref[container-page-test-module-Recent+u+impl-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\
+
+\input{test/Recent_impl.B.tex}
diff --git a/test/generators/cases_post408/latex/dune b/test/generators/cases_post408/latex/dune
new file mode 100644
index 0000000000..11244a7204
--- /dev/null
+++ b/test/generators/cases_post408/latex/dune
@@ -0,0 +1 @@
+(include latex.dune.inc)
diff --git a/test/generators/cases_post408/latex/gen_latex/dune b/test/generators/cases_post408/latex/gen_latex/dune
new file mode 100644
index 0000000000..a8328f0f5d
--- /dev/null
+++ b/test/generators/cases_post408/latex/gen_latex/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_latex)
+ (libraries latex_t_rule)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_post408/latex/gen_latex/gen_latex.ml b/test/generators/cases_post408/latex/gen_latex/gen_latex.ml
new file mode 100644
index 0000000000..25c4381bde
--- /dev/null
+++ b/test/generators/cases_post408/latex/gen_latex/gen_latex.ml
@@ -0,0 +1,6 @@
+let () =
+ let stanzas =
+ Gen_backend.gen_backend_rules "latex" Latex_t_rule.latex_target_rule
+ Gen_backend.files "4.08"
+ in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_post408/latex/latex.dune.inc b/test/generators/cases_post408/latex/latex.dune.inc
new file mode 100644
index 0000000000..303aee7ed3
--- /dev/null
+++ b/test/generators/cases_post408/latex/latex.dune.inc
@@ -0,0 +1,96 @@
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../bugs_post_406.odocl})
+ (with-stdout-to
+ Bugs_post_406.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Bugs_post_406.tex'")))
+ (with-stdout-to
+ Bugs_post_406.let_open'.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Bugs_post_406.let_open'\\''.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_post_406.tex Bugs_post_406.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_post_406.let_open'.tex Bugs_post_406.let_open'.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../labels.odocl})
+ (with-stdout-to
+ Labels.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Labels.tex'")))
+ (with-stdout-to
+ Labels.c.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Labels.c.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.tex Labels.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.c.tex Labels.c.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../recent.odocl})
+ (with-stdout-to
+ Recent.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Recent.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.tex Recent.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../recent_impl.odocl})
+ (with-stdout-to
+ Recent_impl.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Recent_impl.tex'")))
+ (with-stdout-to
+ Recent_impl.B.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Recent_impl.B.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.tex Recent_impl.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.B.tex Recent_impl.B.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
diff --git a/test/generators/cases_post408/link.dune.inc b/test/generators/cases_post408/link.dune.inc
new file mode 100644
index 0000000000..e5783f544c
--- /dev/null
+++ b/test/generators/cases_post408/link.dune.inc
@@ -0,0 +1,134 @@
+(rule
+ (target bugs_post_406.cmti)
+ (deps cases/bugs_post_406.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target bugs_post_406.odoc)
+ (deps bugs_post_406.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target bugs_post_406.odocl)
+ (deps bugs_post_406.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target labels.cmti)
+ (deps cases/labels.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target labels.odoc)
+ (deps labels.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target labels.odocl)
+ (deps labels.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target recent.cmti)
+ (deps cases/recent.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target recent.odoc)
+ (deps recent.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target recent.odocl)
+ (deps recent.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target recent_impl.cmt)
+ (deps cases/recent_impl.ml)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target recent_impl.odoc)
+ (deps recent_impl.cmt)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target recent_impl.odocl)
+ (deps recent_impl.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(subdir
+ html
+ (rule
+ (with-stdout-to
+ html.dune.inc.gen
+ (pipe-stdout
+ (run
+ gen_html/gen_html.exe
+ %{dep:../bugs_post_406.odocl}
+ %{dep:../labels.odocl}
+ %{dep:../recent.odocl}
+ %{dep:../recent_impl.odocl})
+ (run dune format-dune-file)))))
+
+(subdir
+ latex
+ (rule
+ (with-stdout-to
+ latex.dune.inc.gen
+ (pipe-stdout
+ (run
+ gen_latex/gen_latex.exe
+ %{dep:../bugs_post_406.odocl}
+ %{dep:../labels.odocl}
+ %{dep:../recent.odocl}
+ %{dep:../recent_impl.odocl})
+ (run dune format-dune-file)))))
+
+(subdir
+ man
+ (rule
+ (with-stdout-to
+ man.dune.inc.gen
+ (pipe-stdout
+ (run
+ gen_man/gen_man.exe
+ %{dep:../bugs_post_406.odocl}
+ %{dep:../labels.odocl}
+ %{dep:../recent.odocl}
+ %{dep:../recent_impl.odocl})
+ (run dune format-dune-file)))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff html/html.dune.inc html/html.dune.inc.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff latex/latex.dune.inc latex/latex.dune.inc.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff man/man.dune.inc man/man.dune.inc.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
diff --git a/test/generators/cases_post408/man/Bugs_post_406.3o b/test/generators/cases_post408/man/Bugs_post_406.3o
new file mode 100644
index 0000000000..3e51aee056
--- /dev/null
+++ b/test/generators/cases_post408/man/Bugs_post_406.3o
@@ -0,0 +1,19 @@
+
+.TH Bugs_post_406 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Bugs_post_406
+.SH Synopsis
+.sp
+.in 2
+\fBModule Bugs_post_406\fR
+.in
+.sp
+.fi
+Let-open in class types, https://github\.com/ocaml/odoc/issues/543 This was added to the language in 4\.06
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]class\fR \f[CB]type\fR let_open = \f[CB]object\fR \f[CB]end\fR
+.sp
+\f[CB]class\fR let_open' : \f[CB]object\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_post408/man/Bugs_post_406.let_open'.3o b/test/generators/cases_post408/man/Bugs_post_406.let_open'.3o
new file mode 100644
index 0000000000..08c57488d3
--- /dev/null
+++ b/test/generators/cases_post408/man/Bugs_post_406.let_open'.3o
@@ -0,0 +1,14 @@
+
+.TH let_open' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Bugs_post_406\.let_open'
+.SH Synopsis
+.sp
+.in 2
+\fBClass Bugs_post_406\.let_open'\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_post408/man/Labels.3o b/test/generators/cases_post408/man/Labels.3o
new file mode 100644
index 0000000000..a47d1dd2c7
--- /dev/null
+++ b/test/generators/cases_post408/man/Labels.3o
@@ -0,0 +1,154 @@
+
+.TH Labels 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Labels
+.SH Synopsis
+.sp
+.in 2
+\fBModule Labels\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Attached to unit\fR
+.in
+.sp
+.in 3
+\fB2 Attached to nothing\fR
+.in
+.sp
+\f[CB]module\fR A : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR t
+.fi
+.br
+.ti +2
+Attached to type
+.nf
+.sp
+\f[CB]val\fR f : t
+.fi
+.br
+.ti +2
+Attached to value
+.nf
+.sp
+\f[CB]val\fR e : unit \f[CB]\->\fR t
+.fi
+.br
+.ti +2
+Attached to external
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+.sp
+.ti +2
+\fB2\.1\.1 Attached to module type\fR
+.sp
+.ti +2
+
+.br
+\f[CB]end\fR
+.sp
+\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]class\fR \f[CB]type\fR cs = \f[CB]object\fR
+.br
+.ti +2
+.sp
+.ti +2
+\fB2\.1\.2 Attached to class type\fR
+.sp
+.ti +2
+
+.br
+\f[CB]end\fR
+.sp
+\f[CB]exception\fR \f[CB]E\fR
+.fi
+.br
+.ti +2
+Attached to exception
+.nf
+.sp
+\f[CB]type\fR x = \.\.
+.sp
+\f[CB]type\fR x +=
+.br
+.ti +2
+| \f[CB]X\fR
+.br
+.fi
+.br
+.ti +2
+Attached to extension
+.nf
+.sp
+\f[CB]module\fR S := A
+.fi
+.br
+.ti +2
+Attached to module subst
+.nf
+.sp
+\f[CB]type\fR s := t
+.fi
+.br
+.ti +2
+Attached to type subst
+.nf
+.sp
+\f[CB]type\fR u =
+.br
+.ti +2
+| \f[CB]A'\fR
+.br
+.ti +4
+(* Attached to constructor *)
+.br
+.sp
+\f[CB]type\fR v = {
+.br
+.ti +2
+f : t;
+.br
+.ti +4
+(* Attached to field *)
+.br
+}
+.sp
+.fi
+Testing that labels can be referenced
+.sp
+\(bu \f[CI]Attached to unit\fR
+.br
+\(bu \f[CI]Attached to nothing\fR
+.br
+\(bu \f[CI]Attached to module\fR
+.br
+\(bu \f[CI]Attached to type\fR
+.br
+\(bu \f[CI]Attached to value\fR
+.br
+\(bu \f[CI]Attached to class\fR
+.br
+\(bu \f[CI]Attached to class type\fR
+.br
+\(bu \f[CI]Attached to exception\fR
+.br
+\(bu \f[CI]Attached to extension\fR
+.br
+\(bu \f[CI]Attached to module subst\fR
+.br
+\(bu \f[CI]Attached to type subst\fR
+.br
+\(bu \f[CI]Attached to constructor\fR
+.br
+\(bu \f[CI]Attached to field\fR
+.nf
+
diff --git a/test/generators/cases_post408/man/Labels.A.3o b/test/generators/cases_post408/man/Labels.A.3o
new file mode 100644
index 0000000000..2c9d46167a
--- /dev/null
+++ b/test/generators/cases_post408/man/Labels.A.3o
@@ -0,0 +1,19 @@
+
+.TH A 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Labels\.A
+.SH Synopsis
+.sp
+.in 2
+\fBModule Labels\.A\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Attached to module\fR
+.in
+.sp
+
diff --git a/test/generators/cases_post408/man/Labels.c.3o b/test/generators/cases_post408/man/Labels.c.3o
new file mode 100644
index 0000000000..b978bba39b
--- /dev/null
+++ b/test/generators/cases_post408/man/Labels.c.3o
@@ -0,0 +1,19 @@
+
+.TH c 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Labels\.c
+.SH Synopsis
+.sp
+.in 2
+\fBClass Labels\.c\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Attached to class\fR
+.in
+.sp
+
diff --git a/test/man/expect/test_package+ml/Recent.3o b/test/generators/cases_post408/man/Recent.3o
similarity index 98%
rename from test/man/expect/test_package+ml/Recent.3o
rename to test/generators/cases_post408/man/Recent.3o
index bb5dd5de24..9a39f34861 100644
--- a/test/man/expect/test_package+ml/Recent.3o
+++ b/test/generators/cases_post408/man/Recent.3o
@@ -1,7 +1,7 @@
.TH Recent 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Recent
+test\.Recent
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Recent.X.3o b/test/generators/cases_post408/man/Recent.X.3o
similarity index 90%
rename from test/man/expect/test_package+ml/Recent.X.3o
rename to test/generators/cases_post408/man/Recent.X.3o
index 826574ac98..855ef065cc 100644
--- a/test/man/expect/test_package+ml/Recent.X.3o
+++ b/test/generators/cases_post408/man/Recent.X.3o
@@ -1,7 +1,7 @@
.TH X 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Recent\.X
+test\.Recent\.X
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_post408/man/Recent.Z.3o b/test/generators/cases_post408/man/Recent.Z.3o
new file mode 100644
index 0000000000..f1ec72167b
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent.Z.3o
@@ -0,0 +1,14 @@
+
+.TH Z 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent\.Z
+.SH Synopsis
+.sp
+.in 2
+\fBModule Recent\.Z\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Y : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_post408/man/Recent.Z.Y.3o b/test/generators/cases_post408/man/Recent.Z.Y.3o
new file mode 100644
index 0000000000..1b966f15c2
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent.Z.Y.3o
@@ -0,0 +1,14 @@
+
+.TH Y 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent\.Z\.Y
+.SH Synopsis
+.sp
+.in 2
+\fBModule Z\.Y\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR X : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_post408/man/Recent.Z.Y.X.3o b/test/generators/cases_post408/man/Recent.Z.Y.X.3o
new file mode 100644
index 0000000000..768815611b
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent.Z.Y.X.3o
@@ -0,0 +1,14 @@
+
+.TH X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent\.Z\.Y\.X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Y\.X\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR 'a t
diff --git a/test/man/expect/test_package+ml/Recent_impl.3o b/test/generators/cases_post408/man/Recent_impl.3o
similarity index 96%
rename from test/man/expect/test_package+ml/Recent_impl.3o
rename to test/generators/cases_post408/man/Recent_impl.3o
index 837c6276b6..8a96555a74 100644
--- a/test/man/expect/test_package+ml/Recent_impl.3o
+++ b/test/generators/cases_post408/man/Recent_impl.3o
@@ -1,7 +1,7 @@
.TH Recent_impl 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Recent_impl
+test\.Recent_impl
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_post408/man/Recent_impl.B.3o b/test/generators/cases_post408/man/Recent_impl.B.3o
new file mode 100644
index 0000000000..42053e03b2
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent_impl.B.3o
@@ -0,0 +1,19 @@
+
+.TH B 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent_impl\.B
+.SH Synopsis
+.sp
+.in 2
+\fBModule Recent_impl\.B\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t =
+.br
+.ti +2
+| \f[CB]B\fR
+.br
+
diff --git a/test/generators/cases_post408/man/Recent_impl.Foo.3o b/test/generators/cases_post408/man/Recent_impl.Foo.3o
new file mode 100644
index 0000000000..5fcdcef7e2
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent_impl.Foo.3o
@@ -0,0 +1,16 @@
+
+.TH Foo 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent_impl\.Foo
+.SH Synopsis
+.sp
+.in 2
+\fBModule Recent_impl\.Foo\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR A : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR B : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_post408/man/Recent_impl.Foo.A.3o b/test/generators/cases_post408/man/Recent_impl.Foo.A.3o
new file mode 100644
index 0000000000..bd5b2f356b
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent_impl.Foo.A.3o
@@ -0,0 +1,19 @@
+
+.TH A 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent_impl\.Foo\.A
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.A\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t =
+.br
+.ti +2
+| \f[CB]A\fR
+.br
+
diff --git a/test/generators/cases_post408/man/Recent_impl.Foo.B.3o b/test/generators/cases_post408/man/Recent_impl.Foo.B.3o
new file mode 100644
index 0000000000..b2c134e56f
--- /dev/null
+++ b/test/generators/cases_post408/man/Recent_impl.Foo.B.3o
@@ -0,0 +1,19 @@
+
+.TH B 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Recent_impl\.Foo\.B
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.B\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t =
+.br
+.ti +2
+| \f[CB]B\fR
+.br
+
diff --git a/test/generators/cases_post408/man/dune b/test/generators/cases_post408/man/dune
new file mode 100644
index 0000000000..985a2da3ef
--- /dev/null
+++ b/test/generators/cases_post408/man/dune
@@ -0,0 +1 @@
+(include man.dune.inc)
diff --git a/test/generators/cases_post408/man/gen_man/dune b/test/generators/cases_post408/man/gen_man/dune
new file mode 100644
index 0000000000..c282dcce51
--- /dev/null
+++ b/test/generators/cases_post408/man/gen_man/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_man)
+ (libraries man_t_rule)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_post408/man/gen_man/gen_man.ml b/test/generators/cases_post408/man/gen_man/gen_man.ml
new file mode 100644
index 0000000000..68f17be506
--- /dev/null
+++ b/test/generators/cases_post408/man/gen_man/gen_man.ml
@@ -0,0 +1,6 @@
+let () =
+ let stanzas =
+ Gen_backend.gen_backend_rules "man" Man_t_rule.man_target_rule
+ Gen_backend.files "4.08"
+ in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_post408/man/man.dune.inc b/test/generators/cases_post408/man/man.dune.inc
new file mode 100644
index 0000000000..565f2352ed
--- /dev/null
+++ b/test/generators/cases_post408/man/man.dune.inc
@@ -0,0 +1,184 @@
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../bugs_post_406.odocl})
+ (with-stdout-to
+ Bugs_post_406.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Bugs_post_406.3o'")))
+ (with-stdout-to
+ Bugs_post_406.let_open'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Bugs_post_406.let_open'\\''.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_post_406.3o Bugs_post_406.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_post_406.let_open'.3o Bugs_post_406.let_open'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../labels.odocl})
+ (with-stdout-to
+ Labels.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Labels.3o'")))
+ (with-stdout-to
+ Labels.A.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Labels.A.3o'")))
+ (with-stdout-to
+ Labels.c.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Labels.c.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.3o Labels.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.A.3o Labels.A.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Labels.c.3o Labels.c.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../recent.odocl})
+ (with-stdout-to
+ Recent.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent.3o'")))
+ (with-stdout-to
+ Recent.Z.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent.Z.3o'")))
+ (with-stdout-to
+ Recent.Z.Y.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent.Z.Y.3o'")))
+ (with-stdout-to
+ Recent.Z.Y.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent.Z.Y.X.3o'")))
+ (with-stdout-to
+ Recent.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent.X.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.3o Recent.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.Z.3o Recent.Z.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.Z.Y.3o Recent.Z.Y.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.Z.Y.X.3o Recent.Z.Y.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent.X.3o Recent.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../recent_impl.odocl})
+ (with-stdout-to
+ Recent_impl.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent_impl.3o'")))
+ (with-stdout-to
+ Recent_impl.Foo.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent_impl.Foo.3o'")))
+ (with-stdout-to
+ Recent_impl.Foo.A.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent_impl.Foo.A.3o'")))
+ (with-stdout-to
+ Recent_impl.Foo.B.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent_impl.Foo.B.3o'")))
+ (with-stdout-to
+ Recent_impl.B.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Recent_impl.B.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.3o Recent_impl.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.Foo.3o Recent_impl.Foo.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.Foo.A.3o Recent_impl.Foo.A.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.Foo.B.3o Recent_impl.Foo.B.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Recent_impl.B.3o Recent_impl.B.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.08)))
diff --git a/test/generators/cases_pre408/cases/.ocamlformat b/test/generators/cases_pre408/cases/.ocamlformat
new file mode 100644
index 0000000000..4d6556cb8b
--- /dev/null
+++ b/test/generators/cases_pre408/cases/.ocamlformat
@@ -0,0 +1 @@
+disable = true
diff --git a/test/cases/alias.ml b/test/generators/cases_pre408/cases/alias.ml
similarity index 100%
rename from test/cases/alias.ml
rename to test/generators/cases_pre408/cases/alias.ml
diff --git a/test/cases/bugs.ml b/test/generators/cases_pre408/cases/bugs.ml
similarity index 100%
rename from test/cases/bugs.ml
rename to test/generators/cases_pre408/cases/bugs.ml
diff --git a/test/cases/bugs_pre_410.ml b/test/generators/cases_pre408/cases/bugs_pre_410.ml
similarity index 100%
rename from test/cases/bugs_pre_410.ml
rename to test/generators/cases_pre408/cases/bugs_pre_410.ml
diff --git a/test/cases/class.mli b/test/generators/cases_pre408/cases/class.mli
similarity index 100%
rename from test/cases/class.mli
rename to test/generators/cases_pre408/cases/class.mli
diff --git a/test/cases/external.mli b/test/generators/cases_pre408/cases/external.mli
similarity index 100%
rename from test/cases/external.mli
rename to test/generators/cases_pre408/cases/external.mli
diff --git a/test/cases/functor.mli b/test/generators/cases_pre408/cases/functor.mli
similarity index 100%
rename from test/cases/functor.mli
rename to test/generators/cases_pre408/cases/functor.mli
diff --git a/test/cases/functor2.mli b/test/generators/cases_pre408/cases/functor2.mli
similarity index 100%
rename from test/cases/functor2.mli
rename to test/generators/cases_pre408/cases/functor2.mli
diff --git a/test/cases/include.mli b/test/generators/cases_pre408/cases/include.mli
similarity index 100%
rename from test/cases/include.mli
rename to test/generators/cases_pre408/cases/include.mli
diff --git a/test/cases/include2.ml b/test/generators/cases_pre408/cases/include2.ml
similarity index 100%
rename from test/cases/include2.ml
rename to test/generators/cases_pre408/cases/include2.ml
diff --git a/test/cases/include_sections.mli b/test/generators/cases_pre408/cases/include_sections.mli
similarity index 100%
rename from test/cases/include_sections.mli
rename to test/generators/cases_pre408/cases/include_sections.mli
diff --git a/test/cases/interlude.mli b/test/generators/cases_pre408/cases/interlude.mli
similarity index 100%
rename from test/cases/interlude.mli
rename to test/generators/cases_pre408/cases/interlude.mli
diff --git a/test/cases/markup.mli b/test/generators/cases_pre408/cases/markup.mli
similarity index 100%
rename from test/cases/markup.mli
rename to test/generators/cases_pre408/cases/markup.mli
diff --git a/test/cases/mld.mld b/test/generators/cases_pre408/cases/mld.mld
similarity index 100%
rename from test/cases/mld.mld
rename to test/generators/cases_pre408/cases/mld.mld
diff --git a/test/cases/module.mli b/test/generators/cases_pre408/cases/module.mli
similarity index 100%
rename from test/cases/module.mli
rename to test/generators/cases_pre408/cases/module.mli
diff --git a/test/cases/nested.mli b/test/generators/cases_pre408/cases/nested.mli
similarity index 100%
rename from test/cases/nested.mli
rename to test/generators/cases_pre408/cases/nested.mli
diff --git a/test/generators/cases_pre408/cases/ocamlary.mli b/test/generators/cases_pre408/cases/ocamlary.mli
new file mode 120000
index 0000000000..71395fad4c
--- /dev/null
+++ b/test/generators/cases_pre408/cases/ocamlary.mli
@@ -0,0 +1 @@
+../../../../src/ocamlary/ocamlary.mli
\ No newline at end of file
diff --git a/test/cases/section.mli b/test/generators/cases_pre408/cases/section.mli
similarity index 100%
rename from test/cases/section.mli
rename to test/generators/cases_pre408/cases/section.mli
diff --git a/test/cases/stop.mli b/test/generators/cases_pre408/cases/stop.mli
similarity index 100%
rename from test/cases/stop.mli
rename to test/generators/cases_pre408/cases/stop.mli
diff --git a/test/cases/stop_dead_link_doc.mli b/test/generators/cases_pre408/cases/stop_dead_link_doc.mli
similarity index 100%
rename from test/cases/stop_dead_link_doc.mli
rename to test/generators/cases_pre408/cases/stop_dead_link_doc.mli
diff --git a/test/cases/toplevel_comments.mli b/test/generators/cases_pre408/cases/toplevel_comments.mli
similarity index 87%
rename from test/cases/toplevel_comments.mli
rename to test/generators/cases_pre408/cases/toplevel_comments.mli
index 342a884c87..93dc362a58 100644
--- a/test/cases/toplevel_comments.mli
+++ b/test/generators/cases_pre408/cases/toplevel_comments.mli
@@ -70,12 +70,3 @@ class type ct =
class c2 : ct
(** Doc of [c2]. *)
-
-module Ref_in_synopsis : sig
- (** {!t}.
-
- This reference should resolve in the context of this module, even when
- used as a synopsis. *)
-
- type t
-end
diff --git a/test/cases/type.mli b/test/generators/cases_pre408/cases/type.mli
similarity index 100%
rename from test/cases/type.mli
rename to test/generators/cases_pre408/cases/type.mli
diff --git a/test/cases/val.mli b/test/generators/cases_pre408/cases/val.mli
similarity index 100%
rename from test/cases/val.mli
rename to test/generators/cases_pre408/cases/val.mli
diff --git a/test/generators/cases_pre408/dune b/test/generators/cases_pre408/dune
new file mode 100644
index 0000000000..8c968778d9
--- /dev/null
+++ b/test/generators/cases_pre408/dune
@@ -0,0 +1,20 @@
+(include link.dune.inc)
+
+(rule
+ (deps
+ (glob_files cases/*))
+ (enabled_if
+ (>= %{ocaml_version} 4.10))
+ (action
+ (with-stdout-to
+ link.dune.inc.gen
+ (pipe-stdout
+ (run gen_link/gen_link.exe)
+ (run dune format-dune-file)))))
+
+(rule
+ (enabled_if
+ (>= %{ocaml_version} 4.10))
+ (alias runtest)
+ (action
+ (diff link.dune.inc link.dune.inc.gen)))
diff --git a/test/generators/cases_pre408/gen_link/dune b/test/generators/cases_pre408/gen_link/dune
new file mode 100644
index 0000000000..7579f2ecf2
--- /dev/null
+++ b/test/generators/cases_pre408/gen_link/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_link)
+ (libraries gen_link_lib)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_pre408/gen_link/gen_link.ml b/test/generators/cases_pre408/gen_link/gen_link.ml
new file mode 100644
index 0000000000..ec5ce2aec6
--- /dev/null
+++ b/test/generators/cases_pre408/gen_link/gen_link.ml
@@ -0,0 +1,9 @@
+let () =
+ let paths =
+ Gen_link_lib.read_file_from_dir (Fpath.filename Gen_link_lib.cases)
+ in
+ let paths =
+ List.filter (fun p -> not (Gen_link_lib.is_dot_ocamlformat p)) paths
+ in
+ let stanzas = Gen_link_lib.gen_rule paths "4.10" in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_pre408/html/Alias.Foo__X.index.html b/test/generators/cases_pre408/html/Alias.Foo__X.index.html
new file mode 100644
index 0000000000..df1eea8b04
--- /dev/null
+++ b/test/generators/cases_pre408/html/Alias.Foo__X.index.html
@@ -0,0 +1,34 @@
+
+
+ Foo__X (test.Alias.Foo__X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Alias » Foo__X
+
+
+
+
+
+
+
Module Foo__X documentation. This should appear in the documentation
+ for the alias to this module 'X'
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Alias.X.index.html b/test/generators/cases_pre408/html/Alias.X.index.html
new file mode 100644
index 0000000000..19b7adae56
--- /dev/null
+++ b/test/generators/cases_pre408/html/Alias.X.index.html
@@ -0,0 +1,34 @@
+
+
+ X (test.Alias.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Alias » X
+
+
+
+
+
+
+
Module Foo__X documentation. This should appear in the documentation
+ for the alias to this module 'X'
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Alias.index.html b/test/generators/cases_pre408/html/Alias.index.html
new file mode 100644
index 0000000000..6d0ce1821a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Alias.index.html
@@ -0,0 +1,42 @@
+
+
+ Alias (test.Alias)
+
+
+
+
+
+
+
+ Up –
+ test » Alias
+
+
+
+
+
+
+
module
+ Foo__X
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Bugs.index.html b/test/generators/cases_pre408/html/Bugs.index.html
new file mode 100644
index 0000000000..183984135f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Bugs.index.html
@@ -0,0 +1,48 @@
+
+
+ Bugs (test.Bugs)
+
+
+
+
+
+
+
+ Up –
+ test » Bugs
+
+
+
+
+
+
+
type 'a opt
+ = 'a option
+
+
+
+
+
+
+
+ val foo :
+ ?bar:'a
+ ->
+ unit ->
+ unit
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Bugs_pre_410.index.html b/test/generators/cases_pre408/html/Bugs_pre_410.index.html
new file mode 100644
index 0000000000..29263f8686
--- /dev/null
+++ b/test/generators/cases_pre408/html/Bugs_pre_410.index.html
@@ -0,0 +1,49 @@
+
+
+ Bugs_pre_410 (test.Bugs_pre_410)
+
+
+
+
+
+
+
+ Up –
+ test » Bugs_pre_410
+
+
+
+
+
+
+
+ type 'a opt'
+ = int option
+
+
+
+
+
+
+
+ val foo' :
+ ?bar:int ->
+ unit -> unit
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-empty_virtual'.index.html b/test/generators/cases_pre408/html/Class.class-empty_virtual'.index.html
new file mode 100644
index 0000000000..c91e90333d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-empty_virtual'.index.html
@@ -0,0 +1,19 @@
+
+
+ empty_virtual' (test.Class.empty_virtual')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » empty_virtual'
+
+
+ Class Class.empty_virtual'
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-mutually'.index.html b/test/generators/cases_pre408/html/Class.class-mutually'.index.html
new file mode 100644
index 0000000000..991f72872b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-mutually'.index.html
@@ -0,0 +1,19 @@
+
+
+ mutually' (test.Class.mutually')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » mutually'
+
+
+ Class Class.mutually'
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-polymorphic'.index.html b/test/generators/cases_pre408/html/Class.class-polymorphic'.index.html
new file mode 100644
index 0000000000..fca66ee3ee
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-polymorphic'.index.html
@@ -0,0 +1,19 @@
+
+
+ polymorphic' (test.Class.polymorphic')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » polymorphic'
+
+
+ Class Class.polymorphic'
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-recursive'.index.html b/test/generators/cases_pre408/html/Class.class-recursive'.index.html
new file mode 100644
index 0000000000..f01ad22ad9
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-recursive'.index.html
@@ -0,0 +1,19 @@
+
+
+ recursive' (test.Class.recursive')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » recursive'
+
+
+ Class Class.recursive'
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-type-empty.index.html b/test/generators/cases_pre408/html/Class.class-type-empty.index.html
new file mode 100644
index 0000000000..c55ff33b66
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-type-empty.index.html
@@ -0,0 +1,19 @@
+
+
+ empty (test.Class.empty)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » empty
+
+
+ Class type Class.empty
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-type-empty_virtual.index.html b/test/generators/cases_pre408/html/Class.class-type-empty_virtual.index.html
new file mode 100644
index 0000000000..d9feeec2a8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-type-empty_virtual.index.html
@@ -0,0 +1,19 @@
+
+
+ empty_virtual (test.Class.empty_virtual)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » empty_virtual
+
+
+ Class type Class.empty_virtual
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-type-mutually.index.html b/test/generators/cases_pre408/html/Class.class-type-mutually.index.html
new file mode 100644
index 0000000000..39a8c0708d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-type-mutually.index.html
@@ -0,0 +1,19 @@
+
+
+ mutually (test.Class.mutually)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » mutually
+
+
+ Class type Class.mutually
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-type-polymorphic.index.html b/test/generators/cases_pre408/html/Class.class-type-polymorphic.index.html
new file mode 100644
index 0000000000..0791a1fc36
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-type-polymorphic.index.html
@@ -0,0 +1,19 @@
+
+
+ polymorphic (test.Class.polymorphic)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » polymorphic
+
+
+ Class type Class.polymorphic
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.class-type-recursive.index.html b/test/generators/cases_pre408/html/Class.class-type-recursive.index.html
new file mode 100644
index 0000000000..df4bdb5482
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.class-type-recursive.index.html
@@ -0,0 +1,19 @@
+
+
+ recursive (test.Class.recursive)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Class » recursive
+
+
+ Class type Class.recursive
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Class.index.html b/test/generators/cases_pre408/html/Class.index.html
new file mode 100644
index 0000000000..ddb44c9e37
--- /dev/null
+++ b/test/generators/cases_pre408/html/Class.index.html
@@ -0,0 +1,135 @@
+
+
+ Class (test.Class)
+
+
+
+
+
+
+
+ Up –
+ test » Class
+
+
+
+
+
+
+
+ class
+ type
+ empty
+ = object ...
+ end
+
+
+
+
+
+
+
+
+ class
+ type
+
+ mutually
+ = object ...
+ end
+
+
+
+
+
+
+
+
+ class
+ type
+
+ recursive
+ = object ...
+ end
+
+
+
+
+
+
+
+
+
+ class
+ type virtual
+
+
+ empty_virtual
+
+ = object ...
+ end
+
+
+
+
+
+
+
+
+
+ class
+ type 'a
+
+ polymorphic
+
+ = object ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/External.index.html b/test/generators/cases_pre408/html/External.index.html
new file mode 100644
index 0000000000..682f7639f1
--- /dev/null
+++ b/test/generators/cases_pre408/html/External.index.html
@@ -0,0 +1,30 @@
+
+
+ External (test.External)
+
+
+
+
+
+
+
+ Up –
+ test » External
+
+
+
+
+
+
+
+ val foo :
+ unit -> unit
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F1.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Functor.F1.argument-1-Arg.index.html
new file mode 100644
index 0000000000..435b9d2580
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F1.argument-1-Arg.index.html
@@ -0,0 +1,28 @@
+
+
+ Arg (test.Functor.F1.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor »
+ F1 » 1-Arg
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F1.index.html b/test/generators/cases_pre408/html/Functor.F1.index.html
new file mode 100644
index 0000000000..d083922658
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F1.index.html
@@ -0,0 +1,44 @@
+
+
+ F1 (test.Functor.F1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » F1
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : S
+
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F2.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Functor.F2.argument-1-Arg.index.html
new file mode 100644
index 0000000000..db266568c4
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F2.argument-1-Arg.index.html
@@ -0,0 +1,28 @@
+
+
+ Arg (test.Functor.F2.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor »
+ F2 » 1-Arg
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F2.index.html b/test/generators/cases_pre408/html/Functor.F2.index.html
new file mode 100644
index 0000000000..f89ad45819
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F2.index.html
@@ -0,0 +1,46 @@
+
+
+ F2 (test.Functor.F2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » F2
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : S
+
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F3.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Functor.F3.argument-1-Arg.index.html
new file mode 100644
index 0000000000..fec5441d80
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F3.argument-1-Arg.index.html
@@ -0,0 +1,28 @@
+
+
+ Arg (test.Functor.F3.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor »
+ F3 » 1-Arg
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F3.index.html b/test/generators/cases_pre408/html/Functor.F3.index.html
new file mode 100644
index 0000000000..25a433743b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F3.index.html
@@ -0,0 +1,46 @@
+
+
+ F3 (test.Functor.F3)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » F3
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : S
+
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F4.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Functor.F4.argument-1-Arg.index.html
new file mode 100644
index 0000000000..cb1e279744
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F4.argument-1-Arg.index.html
@@ -0,0 +1,28 @@
+
+
+ Arg (test.Functor.F4.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor »
+ F4 » 1-Arg
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F4.index.html b/test/generators/cases_pre408/html/Functor.F4.index.html
new file mode 100644
index 0000000000..affda58405
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F4.index.html
@@ -0,0 +1,44 @@
+
+
+ F4 (test.Functor.F4)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » F4
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : S
+
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.F5.index.html b/test/generators/cases_pre408/html/Functor.F5.index.html
new file mode 100644
index 0000000000..9f95548bc5
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.F5.index.html
@@ -0,0 +1,35 @@
+
+
+ F5 (test.Functor.F5)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » F5
+
+
+
+
+
+
+
Parameters
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.index.html b/test/generators/cases_pre408/html/Functor.index.html
new file mode 100644
index 0000000000..2b5eeba09a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.index.html
@@ -0,0 +1,111 @@
+
+
+ Functor (test.Functor)
+
+
+
+
+
+
+
+ Up –
+ test » Functor
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ S1
+ = functor
+ (_
+ : S )
+ ->
+ S
+
+
+
+
+
+
+
+
module
+ F1
+ (Arg :
+ S ) :
+ S
+
+
+
+
+
+
+
+
module
+ F2
+ (Arg :
+ S ) :
+ S
+ with
+ type
+ t =
+ Arg.t
+
+
+
+
+
+
+
+
+
module
+ F3
+ (Arg :
+ S ) :
+ sig ... end
+
+
+
+
+
+
+
+
module
+ F4
+ (Arg :
+ S ) :
+ S
+
+
+
+
+
+
+
+
module
+ F5
+ () : S
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.module-type-S.index.html b/test/generators/cases_pre408/html/Functor.module-type-S.index.html
new file mode 100644
index 0000000000..125ffabbc7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.module-type-S.index.html
@@ -0,0 +1,27 @@
+
+
+ S (test.Functor.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » S
+
+
+ Module type Functor.S
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.module-type-S1.argument-1-_.index.html b/test/generators/cases_pre408/html/Functor.module-type-S1.argument-1-_.index.html
new file mode 100644
index 0000000000..0da2d05f42
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.module-type-S1.argument-1-_.index.html
@@ -0,0 +1,28 @@
+
+
+ _ (test.Functor.S1.1-_)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor »
+ S1 » 1-_
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor.module-type-S1.index.html b/test/generators/cases_pre408/html/Functor.module-type-S1.index.html
new file mode 100644
index 0000000000..4da49126d4
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor.module-type-S1.index.html
@@ -0,0 +1,44 @@
+
+
+ S1 (test.Functor.S1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor » S1
+
+
+ Module type Functor.S1
+
+
+
+
+
+
Parameters
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.X.argument-1-Y.index.html b/test/generators/cases_pre408/html/Functor2.X.argument-1-Y.index.html
new file mode 100644
index 0000000000..88645429d0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.X.argument-1-Y.index.html
@@ -0,0 +1,28 @@
+
+
+ Y (test.Functor2.X.1-Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 »
+ X » 1-Y
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.X.argument-2-Z.index.html b/test/generators/cases_pre408/html/Functor2.X.argument-2-Z.index.html
new file mode 100644
index 0000000000..5f3aec063c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.X.argument-2-Z.index.html
@@ -0,0 +1,28 @@
+
+
+ Z (test.Functor2.X.2-Z)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 »
+ X » 2-Z
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.X.index.html b/test/generators/cases_pre408/html/Functor2.X.index.html
new file mode 100644
index 0000000000..a938f817f7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.X.index.html
@@ -0,0 +1,71 @@
+
+
+ X (test.Functor2.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 » X
+
+
+
+
+
+
+
Parameters
+
+
+
+
Signature
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.index.html b/test/generators/cases_pre408/html/Functor2.index.html
new file mode 100644
index 0000000000..286c0cffd5
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.index.html
@@ -0,0 +1,68 @@
+
+
+ Functor2 (test.Functor2)
+
+
+
+
+
+
+
+ Up –
+ test » Functor2
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
module
+ X
+ (Y :
+ S ) (
+ Z :
+ S ) :
+ sig ... end
+
+
+
+
+
+
+
+
+ module
+ type
+ XF
+ = functor
+ (Y
+ : S )
+ ->
+ functor
+ (Z
+ : S )
+ ->
+ sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.module-type-S.index.html b/test/generators/cases_pre408/html/Functor2.module-type-S.index.html
new file mode 100644
index 0000000000..60fdfaabbc
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.module-type-S.index.html
@@ -0,0 +1,27 @@
+
+
+ S (test.Functor2.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 » S
+
+
+ Module type Functor2.S
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.module-type-XF.argument-1-Y.index.html b/test/generators/cases_pre408/html/Functor2.module-type-XF.argument-1-Y.index.html
new file mode 100644
index 0000000000..27f4585a02
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.module-type-XF.argument-1-Y.index.html
@@ -0,0 +1,28 @@
+
+
+ Y (test.Functor2.XF.1-Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 »
+ XF » 1-Y
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.module-type-XF.argument-2-Z.index.html b/test/generators/cases_pre408/html/Functor2.module-type-XF.argument-2-Z.index.html
new file mode 100644
index 0000000000..9cdb2ac20e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.module-type-XF.argument-2-Z.index.html
@@ -0,0 +1,28 @@
+
+
+ Z (test.Functor2.XF.2-Z)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 »
+ XF » 2-Z
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Functor2.module-type-XF.index.html b/test/generators/cases_pre408/html/Functor2.module-type-XF.index.html
new file mode 100644
index 0000000000..6e4e5ba166
--- /dev/null
+++ b/test/generators/cases_pre408/html/Functor2.module-type-XF.index.html
@@ -0,0 +1,71 @@
+
+
+ XF (test.Functor2.XF)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Functor2 » XF
+
+
+ Module type Functor2.XF
+
+
+
+
+
+
Parameters
+
+
+
+
Signature
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.index.html b/test/generators/cases_pre408/html/Include.index.html
new file mode 100644
index 0000000000..99329fef3c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.index.html
@@ -0,0 +1,246 @@
+
+
+ Include (test.Include)
+
+
+
+
+
+
+
+ Up –
+ test » Include
+
+
+
+
+
+
+ module
+ type
+
+ Not_inlined
+
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+
+ module
+ type
+
+ Inlined
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.module-type-Dorminant_Module.index.html b/test/generators/cases_pre408/html/Include.module-type-Dorminant_Module.index.html
new file mode 100644
index 0000000000..da784c8aa5
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.module-type-Dorminant_Module.index.html
@@ -0,0 +1,53 @@
+
+
+ Dorminant_Module (test.Include.Dorminant_Module)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include » Dorminant_Module
+
+
+ Module type Include.Dorminant_Module
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.module-type-Inherent_Module.index.html b/test/generators/cases_pre408/html/Include.module-type-Inherent_Module.index.html
new file mode 100644
index 0000000000..d6273d8cc6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.module-type-Inherent_Module.index.html
@@ -0,0 +1,31 @@
+
+
+ Inherent_Module (test.Include.Inherent_Module)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include » Inherent_Module
+
+
+ Module type Include.Inherent_Module
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.module-type-Inlined.index.html b/test/generators/cases_pre408/html/Include.module-type-Inlined.index.html
new file mode 100644
index 0000000000..26d4e15828
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.module-type-Inlined.index.html
@@ -0,0 +1,27 @@
+
+
+ Inlined (test.Include.Inlined)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include » Inlined
+
+
+ Module type Include.Inlined
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.module-type-Not_inlined.index.html b/test/generators/cases_pre408/html/Include.module-type-Not_inlined.index.html
new file mode 100644
index 0000000000..cb1d6a5446
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.module-type-Not_inlined.index.html
@@ -0,0 +1,27 @@
+
+
+ Not_inlined (test.Include.Not_inlined)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include » Not_inlined
+
+
+ Module type Include.Not_inlined
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.module-type-Not_inlined_and_closed.index.html b/test/generators/cases_pre408/html/Include.module-type-Not_inlined_and_closed.index.html
new file mode 100644
index 0000000000..90f1c50bff
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.module-type-Not_inlined_and_closed.index.html
@@ -0,0 +1,29 @@
+
+
+
+ Not_inlined_and_closed (test.Include.Not_inlined_and_closed)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include » Not_inlined_and_closed
+
+
+ Module type Include.Not_inlined_and_closed
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include.module-type-Not_inlined_and_opened.index.html b/test/generators/cases_pre408/html/Include.module-type-Not_inlined_and_opened.index.html
new file mode 100644
index 0000000000..3191d0fd39
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include.module-type-Not_inlined_and_opened.index.html
@@ -0,0 +1,29 @@
+
+
+
+ Not_inlined_and_opened (test.Include.Not_inlined_and_opened)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include » Not_inlined_and_opened
+
+
+ Module type Include.Not_inlined_and_opened
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include2.X.index.html b/test/generators/cases_pre408/html/Include2.X.index.html
new file mode 100644
index 0000000000..385f5b3c97
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include2.X.index.html
@@ -0,0 +1,30 @@
+
+
+ X (test.Include2.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include2 » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include2.Y.index.html b/test/generators/cases_pre408/html/Include2.Y.index.html
new file mode 100644
index 0000000000..9ff5367b64
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include2.Y.index.html
@@ -0,0 +1,28 @@
+
+
+ Y (test.Include2.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include2 » Y
+
+
+ Module Include2.Y
+ Top-comment of Y.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include2.Y_include_doc.index.html b/test/generators/cases_pre408/html/Include2.Y_include_doc.index.html
new file mode 100644
index 0000000000..ebbdd18ac0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include2.Y_include_doc.index.html
@@ -0,0 +1,48 @@
+
+
+ Y_include_doc (test.Include2.Y_include_doc)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include2 » Y_include_doc
+
+
+ Module Include2.Y_include_doc
+
+
+
+
+
Doc attached to include Y
. Y
's top-comment
+ shouldn't appear here.
+
+
+
+
+
+ include
+ module type
+ of struct
+ include Y
+ end
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include2.Y_include_synopsis.index.html b/test/generators/cases_pre408/html/Include2.Y_include_synopsis.index.html
new file mode 100644
index 0000000000..f9cee4eb32
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include2.Y_include_synopsis.index.html
@@ -0,0 +1,46 @@
+
+
+ Y_include_synopsis (test.Include2.Y_include_synopsis)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include2 » Y_include_synopsis
+
+
+
+
+
+
+
+ include
+ module type
+ of struct
+ include Y
+ end
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include2.index.html b/test/generators/cases_pre408/html/Include2.index.html
new file mode 100644
index 0000000000..cb60f64c58
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include2.index.html
@@ -0,0 +1,96 @@
+
+
+ Include2 (test.Include2)
+
+
+
+
+
+
+
+ Up –
+ test » Include2
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
Comment about X that should not appear when including X below.
+
+
+
+
+
+
+ include
+ module type
+ of struct
+ include X
+ end
+
+
+
+ Comment about X that should not appear when including X below.
+
+
+
+
+
+
+
module
+ Y
+ : sig ...
+ end
+
+
+
+
+
+
+
+
The include Y
below should have the synopsis from
+ Y
's top-comment attached to it.
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include_sections.index.html b/test/generators/cases_pre408/html/Include_sections.index.html
new file mode 100644
index 0000000000..7fa1021aa6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include_sections.index.html
@@ -0,0 +1,201 @@
+
+
+ Include_sections (test.Include_sections)
+
+
+
+
+
+
+
+ Up –
+ test » Include_sections
+
+
+ Module Include_sections
+
+
+
+
+
+
+
+
+
+ module
+ type
+
+ Something
+ = sig ...
+ end
+
+
+
+
+
Let's include
+ Something
+ once
+
+
+
+
+
+
val something : unit
+
+
+
+
Something
+ 1
+ foo
+
+
Something
+ 2
+
+
+
+ Something 1-bis
+ Some text.
+
+
+ Second include
+
+
Let's include
+ Something
+ a second time: the heading level should be shift here.
+
+
+
+
+
+
val something : unit
+
+
+
+
Something
+ 1
+ foo
+
+
Something
+ 2
+
+
+
+ Something 1-bis
+ Some text.
+
+
+ Third include
+ Shifted some more.
+
+
+
+
+
val something : unit
+
+
+
+
Something
+ 1
+ foo
+
+
Something
+ 2
+
+
+
+ Something 1-bis
+ Some text.
+
+
And let's include it again, but without inlining it this time:
+ the ToC shouldn't grow.
+
+
+
+
+
+ include
+ Something
+
+
+
+
+
+
+
val something : unit
+
+
+
+ Something
+ 1
+ foo
+
+ Something
+ 2
+
+
+
+ Something 1-bis
+ Some text.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Include_sections.module-type-Something.index.html b/test/generators/cases_pre408/html/Include_sections.module-type-Something.index.html
new file mode 100644
index 0000000000..1334c195a3
--- /dev/null
+++ b/test/generators/cases_pre408/html/Include_sections.module-type-Something.index.html
@@ -0,0 +1,55 @@
+
+
+ Something (test.Include_sections.Something)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Include_sections » Something
+
+
+ Module type Include_sections.Something
+ A module type.
+
+
+
+
+
+
+
+
+
val something : unit
+
+
+
+
Something 1
+ foo
+
+
Something 2
+
+
+
+ Something 1-bis
+ Some text.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Interlude.index.html b/test/generators/cases_pre408/html/Interlude.index.html
new file mode 100644
index 0000000000..eb272f1b60
--- /dev/null
+++ b/test/generators/cases_pre408/html/Interlude.index.html
@@ -0,0 +1,57 @@
+
+
+ Interlude (test.Interlude)
+
+
+
+
+
+
+
+ Up –
+ test » Interlude
+
+
+
+
Some separate stray text at the top of the module.
+
+
Some stray text that is not associated with any signature item.
+
It has multiple paragraphs.
+
A separate block of stray text, adjacent to the preceding one.
+
+
+
+
+
val multiple : unit
+
+
+
+
+
+
+
val signature : unit
+
+
+
+
Stray text at the bottom of the module.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Markup.index.html b/test/generators/cases_pre408/html/Markup.index.html
new file mode 100644
index 0000000000..cd48a8cb94
--- /dev/null
+++ b/test/generators/cases_pre408/html/Markup.index.html
@@ -0,0 +1,253 @@
+
+
+ Markup (test.Markup)
+
+
+
+
+
+
+
+ Up –
+ test » Markup
+
+
+
+
+
+
+
Sections
+
Let's get these done first, because sections will be used to break
+ up the rest of this test.
+
Besides the section heading above, there are also
+
+ Subsection headings
+ and
+
+ Sub-subsection
+ headings
+
+
but odoc has banned deeper headings. There are also title headings,
+ but they are only allowed in mld files.
+
Anchors
+
Sections can have attached Anchors , and
+ it is possible to link to them. Links to section
+ headers should not be set in source code style.
+
+
Paragraph
+
Individual paragraphs can have a heading.
+
+ Subparagraph
+
+
Parts of a longer paragraph that can be considered alone can also
+ have headings.
+
Styling
+
This paragraph has some styled elements: bold and italic
+ , bold italic , emphasis ,
+ emphasis within emphasis ,
+ bold italic , superscript , subscript
+ . The line spacing should be enough for superscripts and subscripts
+ not to look odd.
+
+
Note:
+ In italics emphasis is rendered as normal text while
+ emphasis in emphasis is rendered in
+ italics.
+
+ It also work the same in
+ links in italics with
+ emphasis in emphasis .
+
+
+
+
code
is a different kind of markup that doesn't allow
+ nested markup.
+
+
It's possible for two markup elements to appear next to
+ each other and have a space, and appear next to each
+ other with no space. It doesn't matter how much space
+ it was in the source: in this sentence, it was two space characters.
+ And in this one, there is a newline .
+
+
This is also true between non- code
markup
+ and code
.
+
+
Code can appear inside other
markup . Its display
+ shouldn't be affected.
+
+
+ Links and references
+
+
This is a link . It sends you to the top of this
+ page. Links can have markup inside them: bold
+ , italics , emphasis
+ , superscript ,
+ subscript , and
+ code
. Links can also be nested
+ inside markup. Links cannot be nested inside
+ each other. This link has no replacement text: #
+ . The text is filled in by odoc. This is a shorthand link:
+ # . The text is also filled in by odoc in this case.
+
+
This is a reference to foo
.
+ References can have replacement text:
+ the value foo . Except for the special lookup
+ support, references are pretty much just like links. The replacement
+ text can have nested styles: bold ,
+ italic ,
+ emphasis ,
+ superscript ,
+ subscript , and
+ code
. It's also possible to surround
+ a reference in a style: foo
+ . References can't be nested inside references, and links and references
+ can't be nested inside each other.
+
+
+ Preformatted text
+ This is a code block:
+
+
+ let foo = ()
+ (** There are some nested comments in here, but an unpaired comment
+ terminator would terminate the whole doc surrounding comment. It's
+ best to keep code blocks no wider than 72 characters. *)
+
+ let bar =
+ ignore foo
+
+ There are also verbatim blocks:
+
The main difference is these don't get syntax highlighting.
+
Lists
+
This is a shorthand bulleted list,
+ and the paragraphs in each list item support styling .
+ This is a shorthand numbered list.
+
+ Shorthand list items can span multiple lines, however trying
+ to put two paragraphs into a shorthand list item using a double
+ line break
+
+ just creates a paragraph outside the list.
+
Similarly, inserting a blank line between two list items
+
creates two separate lists.
+
but there is also the numbered variant.
+
+
+ lists can be nested
+ and can include references
+ foo
+
+
+ Unicode
+
The parser supports any ASCII-compatible encoding, in particuλar
+ UTF-8.
+
Raw HTML
+
Raw HTML can be as inline
+ elements into sentences.
+
+
+
+ If the raw HTML is the only thing in a paragraph, it is treated as a block
+ element, and won't be wrapped in paragraph tags by the HTML generator.
+
+
+
Modules
+
+
+
Each comment can end with zero or more tags. Here are some examples:
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
Comments in structure items support markup , t
+ o o .
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.M'.index.html b/test/generators/cases_pre408/html/Module.M'.index.html
new file mode 100644
index 0000000000..93843e07a7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.M'.index.html
@@ -0,0 +1,19 @@
+
+
+ M' (test.Module.M')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » M'
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.Mutually.index.html b/test/generators/cases_pre408/html/Module.Mutually.index.html
new file mode 100644
index 0000000000..0cd8d130a1
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.Mutually.index.html
@@ -0,0 +1,19 @@
+
+
+ Mutually (test.Module.Mutually)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » Mutually
+
+
+ Module Module.Mutually
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.Recursive.index.html b/test/generators/cases_pre408/html/Module.Recursive.index.html
new file mode 100644
index 0000000000..923a69e296
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.Recursive.index.html
@@ -0,0 +1,19 @@
+
+
+ Recursive (test.Module.Recursive)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » Recursive
+
+
+ Module Module.Recursive
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.index.html b/test/generators/cases_pre408/html/Module.index.html
new file mode 100644
index 0000000000..f5c353f6da
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.index.html
@@ -0,0 +1,232 @@
+
+
+ Module (test.Module)
+
+
+
+
+
+
+
+ Up –
+ test » Module
+
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ S1
+
+
+
+
+
+
+
+ module
+ type
+ S2
+ = S
+
+
+
+
+
+
+
+ module
+ type
+ S3
+ = S
+ with
+ type
+ t = int
+ and
+ type
+ u = string
+
+
+
+
+
+
+
+
+
+ module
+ type
+ S4
+ = S
+ with
+ type
+ t := int
+
+
+
+
+
+
+
+
+
+ module
+ type
+ S5
+ = S
+ with
+ type
+ 'a v
+ := 'a list
+
+
+
+
+
+
+
+
+
+ type ('a, 'b) result
+
+
+
+
+
+
+
+
+ module
+ type
+ S6
+ = S
+ with
+ type
+ ('a, 'b) w
+ :=
+
+ ('a ,
+ 'b )
+ result
+
+
+
+
+
+
+
+
+
+
module
+ M'
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ S7
+ = S
+ with
+ module
+ M =
+ M'
+
+
+
+
+
+
+
+
+
+ module
+ type
+ S8
+ = S
+ with
+ module
+ M :=
+ M'
+
+
+
+
+
+
+
+
+
+ module
+ type
+ S9
+ = module
+ type of
+ M'
+
+
+
+
+
+
+
+
module
+ Mutually
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Recursive
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S.M.index.html b/test/generators/cases_pre408/html/Module.module-type-S.M.index.html
new file mode 100644
index 0000000000..b2ce5e7f43
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S.M.index.html
@@ -0,0 +1,19 @@
+
+
+ M (test.Module.S.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module »
+ S » M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S.index.html b/test/generators/cases_pre408/html/Module.module-type-S.index.html
new file mode 100644
index 0000000000..acc7c571e8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S.index.html
@@ -0,0 +1,59 @@
+
+
+ S (test.Module.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S
+
+
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S2.M.index.html b/test/generators/cases_pre408/html/Module.module-type-S2.M.index.html
new file mode 100644
index 0000000000..347097bd5e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S2.M.index.html
@@ -0,0 +1,20 @@
+
+
+ M (test.Module.S2.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module »
+ S2 » M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S2.index.html b/test/generators/cases_pre408/html/Module.module-type-S2.index.html
new file mode 100644
index 0000000000..0a1ea74a5d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S2.index.html
@@ -0,0 +1,59 @@
+
+
+ S2 (test.Module.S2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S2
+
+
+ Module type Module.S2
+
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S3.M.index.html b/test/generators/cases_pre408/html/Module.module-type-S3.M.index.html
new file mode 100644
index 0000000000..be99cdd56c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S3.M.index.html
@@ -0,0 +1,20 @@
+
+
+ M (test.Module.S3.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module »
+ S3 » M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S3.index.html b/test/generators/cases_pre408/html/Module.module-type-S3.index.html
new file mode 100644
index 0000000000..5587cf895f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S3.index.html
@@ -0,0 +1,63 @@
+
+
+ S3 (test.Module.S3)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S3
+
+
+ Module type Module.S3
+
+
+
+
+
+
+
type u
+ = string
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S4.M.index.html b/test/generators/cases_pre408/html/Module.module-type-S4.M.index.html
new file mode 100644
index 0000000000..ba66d4d97b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S4.M.index.html
@@ -0,0 +1,20 @@
+
+
+ M (test.Module.S4.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module »
+ S4 » M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S4.index.html b/test/generators/cases_pre408/html/Module.module-type-S4.index.html
new file mode 100644
index 0000000000..7a0012376f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S4.index.html
@@ -0,0 +1,53 @@
+
+
+ S4 (test.Module.S4)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S4
+
+
+ Module type Module.S4
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S5.M.index.html b/test/generators/cases_pre408/html/Module.module-type-S5.M.index.html
new file mode 100644
index 0000000000..421f2773af
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S5.M.index.html
@@ -0,0 +1,20 @@
+
+
+ M (test.Module.S5.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module »
+ S5 » M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S5.index.html b/test/generators/cases_pre408/html/Module.module-type-S5.index.html
new file mode 100644
index 0000000000..afff1edc81
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S5.index.html
@@ -0,0 +1,52 @@
+
+
+ S5 (test.Module.S5)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S5
+
+
+ Module type Module.S5
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S6.M.index.html b/test/generators/cases_pre408/html/Module.module-type-S6.M.index.html
new file mode 100644
index 0000000000..926bfe2e7f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S6.M.index.html
@@ -0,0 +1,20 @@
+
+
+ M (test.Module.S6.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module »
+ S6 » M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S6.index.html b/test/generators/cases_pre408/html/Module.module-type-S6.index.html
new file mode 100644
index 0000000000..5af6741c0f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S6.index.html
@@ -0,0 +1,51 @@
+
+
+ S6 (test.Module.S6)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S6
+
+
+ Module type Module.S6
+
+
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S7.index.html b/test/generators/cases_pre408/html/Module.module-type-S7.index.html
new file mode 100644
index 0000000000..f5099f4c5f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S7.index.html
@@ -0,0 +1,56 @@
+
+
+ S7 (test.Module.S7)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S7
+
+
+ Module type Module.S7
+
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S8.index.html b/test/generators/cases_pre408/html/Module.module-type-S8.index.html
new file mode 100644
index 0000000000..bbfaaa4815
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S8.index.html
@@ -0,0 +1,48 @@
+
+
+ S8 (test.Module.S8)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S8
+
+
+ Module type Module.S8
+
+
+
+
+
+
+
+
+
+ type ('a, 'b) w
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Module.module-type-S9.index.html b/test/generators/cases_pre408/html/Module.module-type-S9.index.html
new file mode 100644
index 0000000000..dc13a95f86
--- /dev/null
+++ b/test/generators/cases_pre408/html/Module.module-type-S9.index.html
@@ -0,0 +1,19 @@
+
+
+ S9 (test.Module.S9)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Module » S9
+
+
+ Module type Module.S9
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.F.argument-1-Arg1.index.html b/test/generators/cases_pre408/html/Nested.F.argument-1-Arg1.index.html
new file mode 100644
index 0000000000..2958e5ca2f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.F.argument-1-Arg1.index.html
@@ -0,0 +1,42 @@
+
+
+ Arg1 (test.Nested.F.1-Arg1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested »
+ F » 1-Arg1
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.F.argument-2-Arg2.index.html b/test/generators/cases_pre408/html/Nested.F.argument-2-Arg2.index.html
new file mode 100644
index 0000000000..45a572b3fa
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.F.argument-2-Arg2.index.html
@@ -0,0 +1,30 @@
+
+
+ Arg2 (test.Nested.F.2-Arg2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested »
+ F » 2-Arg2
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.F.index.html b/test/generators/cases_pre408/html/Nested.F.index.html
new file mode 100644
index 0000000000..799bbe2101
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.F.index.html
@@ -0,0 +1,62 @@
+
+
+ F (test.Nested.F)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested » F
+
+
+
+
+
+
+
Type
+
Parameters
+
+
+
+
+
module
+ Arg1
+ : Y
+
+
+
+
+
+
+
module
+ Arg2
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.X.index.html b/test/generators/cases_pre408/html/Nested.X.index.html
new file mode 100644
index 0000000000..5dedbf5e14
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.X.index.html
@@ -0,0 +1,42 @@
+
+
+ X (test.Nested.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested » X
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.class-inherits.index.html b/test/generators/cases_pre408/html/Nested.class-inherits.index.html
new file mode 100644
index 0000000000..b6df9c0b8d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.class-inherits.index.html
@@ -0,0 +1,30 @@
+
+
+ inherits (test.Nested.inherits)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested » inherits
+
+
+ Class Nested.inherits
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.class-z.index.html b/test/generators/cases_pre408/html/Nested.class-z.index.html
new file mode 100644
index 0000000000..83d5194aaa
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.class-z.index.html
@@ -0,0 +1,58 @@
+
+
+ z (test.Nested.z)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested » z
+
+
+
+
+
+
+
+
+
+
+ val
+ mutable
+ virtual y' : int
+
+
+
+
Methods
+
+
+
+
+
+ method
+ private
+ virtual z' : int
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.index.html b/test/generators/cases_pre408/html/Nested.index.html
new file mode 100644
index 0000000000..a36f2e4022
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.index.html
@@ -0,0 +1,96 @@
+
+
+ Nested (test.Nested)
+
+
+
+
+
+
+
+ Up –
+ test » Nested
+
+
+
+
+
+
+
Module
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
Module type
+
+
+
+
+
+ module
+ type
+ Y
+ = sig ...
+ end
+
+
+
+
Functor
+
+
+
+
module
+ F
+ (Arg1 :
+ Y ) (
+ Arg2 :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
Class
+
+
+
+
+ class
+ virtual
+ z
+ : object ...
+ end
+
+
+
+
+
+
+
+
+ class
+ virtual
+ inherits
+ : object ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Nested.module-type-Y.index.html b/test/generators/cases_pre408/html/Nested.module-type-Y.index.html
new file mode 100644
index 0000000000..9b2a2800f9
--- /dev/null
+++ b/test/generators/cases_pre408/html/Nested.module-type-Y.index.html
@@ -0,0 +1,42 @@
+
+
+ Y (test.Nested.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Nested » Y
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.E.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.E.index.html
new file mode 100644
index 0000000000..a4886afab7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.E.index.html
@@ -0,0 +1,39 @@
+
+
+ E (test.Ocamlary.Aliases.E)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » E
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.A.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.A.index.html
new file mode 100644
index 0000000000..dbbb773d49
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.A.index.html
@@ -0,0 +1,40 @@
+
+
+ A (test.Ocamlary.Aliases.Foo.A)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ Foo » A
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.B.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.B.index.html
new file mode 100644
index 0000000000..b499fb9d05
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.B.index.html
@@ -0,0 +1,40 @@
+
+
+ B (test.Ocamlary.Aliases.Foo.B)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ Foo » B
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.C.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.C.index.html
new file mode 100644
index 0000000000..7a8bc9ee33
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.C.index.html
@@ -0,0 +1,40 @@
+
+
+ C (test.Ocamlary.Aliases.Foo.C)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ Foo » C
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.D.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.D.index.html
new file mode 100644
index 0000000000..6454617260
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.D.index.html
@@ -0,0 +1,40 @@
+
+
+ D (test.Ocamlary.Aliases.Foo.D)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ Foo » D
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.E.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.E.index.html
new file mode 100644
index 0000000000..0af7a5fa80
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.E.index.html
@@ -0,0 +1,40 @@
+
+
+ E (test.Ocamlary.Aliases.Foo.E)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ Foo » E
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.index.html
new file mode 100644
index 0000000000..decdb92a5b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo.index.html
@@ -0,0 +1,77 @@
+
+
+ Foo (test.Ocamlary.Aliases.Foo)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo
+
+
+
+
+
+
+
module
+ A
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ B
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ C
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ D
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ E
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__.index.html
new file mode 100644
index 0000000000..e316fd42bb
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__.index.html
@@ -0,0 +1,62 @@
+
+
+ Foo__ (test.Ocamlary.Aliases.Foo__)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo__
+
+
+
+
+
+
+
module A
+ = Foo__A
+
+
+
+
+
+
+
module B
+ = Foo__B
+
+
+
+
+
+
+
module C
+ = Foo__C
+
+
+
+
+
+
+
module D
+ = Foo__D
+
+
+
+
+
+
+
module E
+ = Foo__E
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__A.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__A.index.html
new file mode 100644
index 0000000000..eeb561a618
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__A.index.html
@@ -0,0 +1,40 @@
+
+
+ Foo__A (test.Ocamlary.Aliases.Foo__A)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo__A
+
+
+ Module Aliases.Foo__A
+
+
+
+
+
+
+
+ val id :
+ t
+ ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__B.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__B.index.html
new file mode 100644
index 0000000000..5ac72c37b8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__B.index.html
@@ -0,0 +1,40 @@
+
+
+ Foo__B (test.Ocamlary.Aliases.Foo__B)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo__B
+
+
+ Module Aliases.Foo__B
+
+
+
+
+
+
+
+ val id :
+ t
+ ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__C.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__C.index.html
new file mode 100644
index 0000000000..2078eb276b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__C.index.html
@@ -0,0 +1,40 @@
+
+
+ Foo__C (test.Ocamlary.Aliases.Foo__C)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo__C
+
+
+ Module Aliases.Foo__C
+
+
+
+
+
+
+
+ val id :
+ t
+ ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__D.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__D.index.html
new file mode 100644
index 0000000000..122cadfc56
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__D.index.html
@@ -0,0 +1,40 @@
+
+
+ Foo__D (test.Ocamlary.Aliases.Foo__D)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo__D
+
+
+ Module Aliases.Foo__D
+
+
+
+
+
+
+
+ val id :
+ t
+ ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__E.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__E.index.html
new file mode 100644
index 0000000000..d0978c4d10
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Foo__E.index.html
@@ -0,0 +1,40 @@
+
+
+ Foo__E (test.Ocamlary.Aliases.Foo__E)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Foo__E
+
+
+ Module Aliases.Foo__E
+
+
+
+
+
+
+
+ val id :
+ t
+ ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.P1.Y.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.P1.Y.index.html
new file mode 100644
index 0000000000..42e2c362f0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.P1.Y.index.html
@@ -0,0 +1,40 @@
+
+
+ Y (test.Ocamlary.Aliases.P1.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ P1 » Y
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.P1.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.P1.index.html
new file mode 100644
index 0000000000..1c46e0ea9e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.P1.index.html
@@ -0,0 +1,33 @@
+
+
+ P1 (test.Ocamlary.Aliases.P1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » P1
+
+
+
+
+
+
+
module
+ Y
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.P2.Z.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.P2.Z.index.html
new file mode 100644
index 0000000000..840992a769
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.P2.Z.index.html
@@ -0,0 +1,40 @@
+
+
+ Z (test.Ocamlary.Aliases.P2.Z)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases »
+ P2 » Z
+
+
+
+
+
+
+
+
+ val id :
+ t ->
+ t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.P2.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.P2.index.html
new file mode 100644
index 0000000000..589c25d085
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.P2.index.html
@@ -0,0 +1,30 @@
+
+
+ P2 (test.Ocamlary.Aliases.P2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » P2
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.Std.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.Std.index.html
new file mode 100644
index 0000000000..d8aaefaa8c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.Std.index.html
@@ -0,0 +1,62 @@
+
+
+ Std (test.Ocamlary.Aliases.Std)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Aliases » Std
+
+
+
+
+
+
+
module A
+ = Foo.A
+
+
+
+
+
+
+
module B
+ = Foo.B
+
+
+
+
+
+
+
module C
+ = Foo.C
+
+
+
+
+
+
+
module D
+ = Foo.D
+
+
+
+
+
+
+
module E
+ = Foo.E
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Aliases.index.html b/test/generators/cases_pre408/html/Ocamlary.Aliases.index.html
new file mode 100644
index 0000000000..5a2d3cc52e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Aliases.index.html
@@ -0,0 +1,290 @@
+
+
+ Aliases (test.Ocamlary.Aliases)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Aliases
+
+
+
+
+
+
+
+
+
module
+ Foo__A
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Foo__B
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Foo__C
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Foo__D
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Foo__E
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Foo__
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Foo
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module A'
+ = Foo.A
+
+
+
+
+
+
+
+
+
+
type tata'
+ = A'.t
+
+
+
+
+
+
+
+
module
+ Std
+ : sig ...
+ end
+
+
+
+
+
include of Foo
+
Just for giggle, let's see what happens when we include
+ Foo
.
+
+
+
+
+
+ include
+ module type
+ of Foo
+
+
+
+
+
+
+
module A
+ = Foo.A
+
+
+
+
+
+
+
module B
+ = Foo.B
+
+
+
+
+
+
+
module C
+ = Foo.C
+
+
+
+
+
+
+
module D
+ = Foo.D
+
+
+
+
+
+
+
module
+ E
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
+
type testa
+ = A.t
+
+
+
+
And also, let's refer to
+ A.t
and
+ Foo.B.id
+
+
+
+
+
module
+ P1
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ P2
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module X1
+ = P2.Z
+
+
+
+
+
+
+
module X2
+ = P2.Z
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Buffer.index.html b/test/generators/cases_pre408/html/Ocamlary.Buffer.index.html
new file mode 100644
index 0000000000..1a5e5c8bb6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Buffer.index.html
@@ -0,0 +1,34 @@
+
+
+ Buffer (test.Ocamlary.Buffer)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Buffer
+
+
+ Module Ocamlary.Buffer
+ Buffer
.t
+
+
+
+
+
+
+ val f :
+ Stdlib .Buffer.t
+ ->
+ unit
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base.List.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base.List.index.html
new file mode 100644
index 0000000000..cea23d7ccb
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base.List.index.html
@@ -0,0 +1,44 @@
+
+
+ List (test.Ocamlary.CanonicalTest.Base.List)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest »
+ Base » List
+
+
+
+
+
+
+
+
+ val id :
+
+ 'a t
+ ->
+
+ 'a t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base.index.html
new file mode 100644
index 0000000000..77f45222a6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base.index.html
@@ -0,0 +1,33 @@
+
+
+ Base (test.Ocamlary.CanonicalTest.Base)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest » Base
+
+
+ Module CanonicalTest.Base
+
+
+
+
+
+
module
+ List
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__.index.html
new file mode 100644
index 0000000000..3493679239
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__.index.html
@@ -0,0 +1,30 @@
+
+
+ Base__ (test.Ocamlary.CanonicalTest.Base__)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest » Base__
+
+
+ Module CanonicalTest.Base__
+
+
+
+
+
+
module List
+ = Base__List
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__List.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__List.index.html
new file mode 100644
index 0000000000..4b0dcd21c1
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__List.index.html
@@ -0,0 +1,46 @@
+
+
+ Base__List (test.Ocamlary.CanonicalTest.Base__List)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest » Base__List
+
+
+ Module CanonicalTest.Base__List
+
+
+
+
+
+
+
+ val id :
+
+ 'a
+ t
+ ->
+
+ 'a
+ t
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__Tests.C.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__Tests.C.index.html
new file mode 100644
index 0000000000..5b83bb8f46
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__Tests.C.index.html
@@ -0,0 +1,47 @@
+
+
+ C (test.Ocamlary.CanonicalTest.Base__Tests.C)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest »
+ Base__Tests » C
+
+
+
+
+
+
+
+
+ val id :
+
+ 'a
+ t
+ ->
+
+ 'a
+ t
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__Tests.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__Tests.index.html
new file mode 100644
index 0000000000..ff6b81d886
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.Base__Tests.index.html
@@ -0,0 +1,99 @@
+
+
+ Base__Tests (test.Ocamlary.CanonicalTest.Base__Tests)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest » Base__Tests
+
+
+ Module CanonicalTest.Base__Tests
+
+
+
+
+
+
module
+ C
+ : module
+ type of
+ Base__ .List
+
+
+
+
+
+
+
+
module L
+ = Base__ .List
+
+
+
+
+
+
+
+ val foo :
+
+ int
+ L .t
+ ->
+
+ float
+ L .t
+
+
+
+
+
+
+
+
+
+ val bar :
+
+ 'a
+ Base__ .List.t
+ ->
+
+ 'a
+ Base__ .List.t
+
+
+
+
+
+
This is just List
.id, or rather L
.id
+
+
+
+
+
+
+ val baz :
+
+ 'a
+ Base__ .List.t
+ ->
+ unit
+
+
+
+
+
Just seeing if Base__
.List.t (Base__.List.t
+ ) gets rewriten to Base
.List.t (Base.List.t
+ )
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.List_modif.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.List_modif.index.html
new file mode 100644
index 0000000000..e6fc5d15ef
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.List_modif.index.html
@@ -0,0 +1,48 @@
+
+
+ List_modif (test.Ocamlary.CanonicalTest.List_modif)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CanonicalTest » List_modif
+
+
+ Module CanonicalTest.List_modif
+
+
+
+
+
+
+
+ val id :
+
+ 'a t
+ ->
+
+ 'a t
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.index.html b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.index.html
new file mode 100644
index 0000000000..0d34f072ee
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CanonicalTest.index.html
@@ -0,0 +1,84 @@
+
+
+ CanonicalTest (test.Ocamlary.CanonicalTest)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » CanonicalTest
+
+
+ Module Ocamlary.CanonicalTest
+
+
+
+
+
+
+
module
+ Base__
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Base
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..f1b2cf092f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+
+ InnerModuleA' (test.Ocamlary.CollectionModule.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CollectionModule »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.index.html
new file mode 100644
index 0000000000..e53a784a25
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.index.html
@@ -0,0 +1,68 @@
+
+
+
+ InnerModuleA (test.Ocamlary.CollectionModule.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CollectionModule » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..f54455ad05
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,38 @@
+
+
+
+
+ InnerModuleTypeA'
+ (test.Ocamlary.CollectionModule.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CollectionModule »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CollectionModule.index.html b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.index.html
new file mode 100644
index 0000000000..a8e75a8c29
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.index.html
@@ -0,0 +1,72 @@
+
+
+ CollectionModule (test.Ocamlary.CollectionModule)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » CollectionModule
+
+
+
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.CollectionModule.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..da199e88bc
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.CollectionModule.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,38 @@
+
+
+
+ InnerModuleTypeA (test.Ocamlary.CollectionModule.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ CollectionModule » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep1.X.Y.class-c.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep1.X.Y.class-c.index.html
new file mode 100644
index 0000000000..a8e841fb24
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep1.X.Y.class-c.index.html
@@ -0,0 +1,29 @@
+
+
+ c (test.Ocamlary.Dep1.X.Y.c)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep1 »
+ X » Y
+ » c
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep1.X.Y.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep1.X.Y.index.html
new file mode 100644
index 0000000000..9d1db976ee
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep1.X.Y.index.html
@@ -0,0 +1,33 @@
+
+
+ Y (test.Ocamlary.Dep1.X.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep1 » X
+ » Y
+
+
+
+
+
+
+
class
+ c
+ : object ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep1.X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep1.X.index.html
new file mode 100644
index 0000000000..7aeef1a096
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep1.X.index.html
@@ -0,0 +1,31 @@
+
+
+ X (test.Ocamlary.Dep1.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep1 » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep1.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep1.index.html
new file mode 100644
index 0000000000..bbcd7acc71
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep1.index.html
@@ -0,0 +1,45 @@
+
+
+ Dep1 (test.Ocamlary.Dep1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep1
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep1.module-type-S.class-c.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep1.module-type-S.class-c.index.html
new file mode 100644
index 0000000000..707f05125d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep1.module-type-S.class-c.index.html
@@ -0,0 +1,28 @@
+
+
+ c (test.Ocamlary.Dep1.S.c)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep1 » S
+ » c
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep1.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep1.module-type-S.index.html
new file mode 100644
index 0000000000..efbc5858a5
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep1.module-type-S.index.html
@@ -0,0 +1,33 @@
+
+
+ S (test.Ocamlary.Dep1.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep1 » S
+
+
+
+
+
+
+
class
+ c
+ : object ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep11.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep11.index.html
new file mode 100644
index 0000000000..a24a09d5c1
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep11.index.html
@@ -0,0 +1,34 @@
+
+
+ Dep11 (test.Ocamlary.Dep11)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep11
+
+
+ Module Ocamlary.Dep11
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep11.module-type-S.class-c.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep11.module-type-S.class-c.index.html
new file mode 100644
index 0000000000..8ffa4158e0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep11.module-type-S.class-c.index.html
@@ -0,0 +1,28 @@
+
+
+ c (test.Ocamlary.Dep11.S.c)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep11 »
+ S » c
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep11.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep11.module-type-S.index.html
new file mode 100644
index 0000000000..e6b15aefa6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep11.module-type-S.index.html
@@ -0,0 +1,33 @@
+
+
+ S (test.Ocamlary.Dep11.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep11 » S
+
+
+
+
+
+
+
class
+ c
+ : object ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep12.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep12.argument-1-Arg.index.html
new file mode 100644
index 0000000000..f19654e817
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep12.argument-1-Arg.index.html
@@ -0,0 +1,32 @@
+
+
+ Arg (test.Ocamlary.Dep12.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep12 » 1-Arg
+
+
+ Parameter Dep12.1-Arg
+
+
+
+
+
+
+ module
+ type
+ S
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep12.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep12.index.html
new file mode 100644
index 0000000000..e953092b42
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep12.index.html
@@ -0,0 +1,52 @@
+
+
+ Dep12 (test.Ocamlary.Dep12)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep12
+
+
+ Module Ocamlary.Dep12
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
+ module
+ type
+ T
+ = Arg.S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep13.class-c.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep13.class-c.index.html
new file mode 100644
index 0000000000..12810fead8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep13.class-c.index.html
@@ -0,0 +1,28 @@
+
+
+ c (test.Ocamlary.Dep13.c)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep13 » c
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep13.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep13.index.html
new file mode 100644
index 0000000000..6fb441a5e4
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep13.index.html
@@ -0,0 +1,32 @@
+
+
+ Dep13 (test.Ocamlary.Dep13)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep13
+
+
+ Module Ocamlary.Dep13
+
+
+
+
+
+
class
+ c
+ : object ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep2.A.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep2.A.index.html
new file mode 100644
index 0000000000..60fc0d7560
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep2.A.index.html
@@ -0,0 +1,31 @@
+
+
+ A (test.Ocamlary.Dep2.A)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep2 » A
+
+
+
+
+
+
+
module Y
+ : Arg.S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep2.argument-1-Arg.X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep2.argument-1-Arg.X.index.html
new file mode 100644
index 0000000000..57f38eabd9
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep2.argument-1-Arg.X.index.html
@@ -0,0 +1,31 @@
+
+
+ X (test.Ocamlary.Dep2.1-Arg.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep2 »
+ 1-Arg » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep2.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep2.argument-1-Arg.index.html
new file mode 100644
index 0000000000..ab6dea957d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep2.argument-1-Arg.index.html
@@ -0,0 +1,43 @@
+
+
+ Arg (test.Ocamlary.Dep2.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep2 » 1-Arg
+
+
+
+
+
+
+
+ module
+ type
+ S
+
+
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep2.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep2.index.html
new file mode 100644
index 0000000000..cd05829209
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep2.index.html
@@ -0,0 +1,59 @@
+
+
+ Dep2 (test.Ocamlary.Dep2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep2
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
module
+ A
+ : sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep3.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep3.index.html
new file mode 100644
index 0000000000..8d201237f3
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep3.index.html
@@ -0,0 +1,27 @@
+
+
+ Dep3 (test.Ocamlary.Dep3)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep3
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep4.X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep4.X.index.html
new file mode 100644
index 0000000000..54afd35d34
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep4.X.index.html
@@ -0,0 +1,28 @@
+
+
+ X (test.Ocamlary.Dep4.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep4 » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep4.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep4.index.html
new file mode 100644
index 0000000000..7f2d09cbb0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep4.index.html
@@ -0,0 +1,56 @@
+
+
+ Dep4 (test.Ocamlary.Dep4)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep4
+
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.X.index.html
new file mode 100644
index 0000000000..0e916de6c8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.X.index.html
@@ -0,0 +1,28 @@
+
+
+ X (test.Ocamlary.Dep4.S.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep4 » S
+ » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.Y.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.Y.index.html
new file mode 100644
index 0000000000..5a333fd9c4
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.Y.index.html
@@ -0,0 +1,20 @@
+
+
+ Y (test.Ocamlary.Dep4.S.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep4 » S
+ » Y
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.index.html
new file mode 100644
index 0000000000..ae8cdee527
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-S.index.html
@@ -0,0 +1,42 @@
+
+
+ S (test.Ocamlary.Dep4.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep4 » S
+
+
+
+
+
+
+
+
module
+ Y
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-T.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-T.index.html
new file mode 100644
index 0000000000..d9c00347ce
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep4.module-type-T.index.html
@@ -0,0 +1,28 @@
+
+
+ T (test.Ocamlary.Dep4.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep4 » T
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep5.Z.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep5.Z.index.html
new file mode 100644
index 0000000000..77789e49a9
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep5.Z.index.html
@@ -0,0 +1,39 @@
+
+
+ Z (test.Ocamlary.Dep5.Z)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep5 » Z
+
+
+
+
+
+
+
module X
+ : Arg.T
+
+
+
+
+
+
+
+
module Y
+ = Dep3
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.index.html
new file mode 100644
index 0000000000..456fe6f9a3
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.index.html
@@ -0,0 +1,53 @@
+
+
+ Arg (test.Ocamlary.Dep5.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep5 » 1-Arg
+
+
+
+
+
+
+
+ module
+ type
+ T
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.index.html
new file mode 100644
index 0000000000..f3691e9f57
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.index.html
@@ -0,0 +1,21 @@
+
+
+ Y (test.Ocamlary.Dep5.1-Arg.S.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep5 »
+ 1-Arg »
+ S » Y
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.module-type-S.index.html
new file mode 100644
index 0000000000..1183b50f63
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep5.argument-1-Arg.module-type-S.index.html
@@ -0,0 +1,42 @@
+
+
+ S (test.Ocamlary.Dep5.1-Arg.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep5 »
+ 1-Arg » S
+
+
+
+
+
+
+
+
module
+ Y
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep5.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep5.index.html
new file mode 100644
index 0000000000..1c180d38a8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep5.index.html
@@ -0,0 +1,55 @@
+
+
+ Dep5 (test.Ocamlary.Dep5)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep5
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
module
+ Z
+ : Arg.S
+ with
+ module
+ Y =
+ Dep3
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.X.Y.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.X.Y.index.html
new file mode 100644
index 0000000000..f5397a4f78
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.X.Y.index.html
@@ -0,0 +1,28 @@
+
+
+ Y (test.Ocamlary.Dep6.X.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » X
+ » Y
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.X.index.html
new file mode 100644
index 0000000000..2335b50e5a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.X.index.html
@@ -0,0 +1,42 @@
+
+
+ X (test.Ocamlary.Dep6.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » X
+
+
+
+
+
+
+
+ module
+ type
+ R
+ = S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.X.module-type-R.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.X.module-type-R.index.html
new file mode 100644
index 0000000000..6d5b3ecfc0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.X.module-type-R.index.html
@@ -0,0 +1,29 @@
+
+
+ R (test.Ocamlary.Dep6.X.R)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » X
+ » R
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.index.html
new file mode 100644
index 0000000000..4f718aa17f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.index.html
@@ -0,0 +1,56 @@
+
+
+ Dep6 (test.Ocamlary.Dep6)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep6
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-S.index.html
new file mode 100644
index 0000000000..24b8be3135
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-S.index.html
@@ -0,0 +1,28 @@
+
+
+ S (test.Ocamlary.Dep6.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » S
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.Y.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.Y.index.html
new file mode 100644
index 0000000000..533068e395
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.Y.index.html
@@ -0,0 +1,28 @@
+
+
+ Y (test.Ocamlary.Dep6.T.Y)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » T
+ » Y
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.index.html
new file mode 100644
index 0000000000..f4578507be
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.index.html
@@ -0,0 +1,42 @@
+
+
+ T (test.Ocamlary.Dep6.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » T
+
+
+
+
+
+
+
+ module
+ type
+ R
+ = S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.module-type-R.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.module-type-R.index.html
new file mode 100644
index 0000000000..3fe1181163
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep6.module-type-T.module-type-R.index.html
@@ -0,0 +1,29 @@
+
+
+ R (test.Ocamlary.Dep6.T.R)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep6 » T
+ » R
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep7.M.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep7.M.index.html
new file mode 100644
index 0000000000..3be847995d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep7.M.index.html
@@ -0,0 +1,42 @@
+
+
+ M (test.Ocamlary.Dep7.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep7 » M
+
+
+
+
+
+
+
+ module
+ type
+ R
+ = Arg.S
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.X.index.html
new file mode 100644
index 0000000000..73cdb5f12e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.X.index.html
@@ -0,0 +1,42 @@
+
+
+ X (test.Ocamlary.Dep7.1-Arg.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep7 »
+ 1-Arg » X
+
+
+
+
+
+
+
+ module
+ type
+ R
+ = S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.index.html
new file mode 100644
index 0000000000..d7030c02f3
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.index.html
@@ -0,0 +1,54 @@
+
+
+ Arg (test.Ocamlary.Dep7.1-Arg)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep7 » 1-Arg
+
+
+
+
+
+
+
+ module
+ type
+ S
+
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.module-type-T.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.module-type-T.index.html
new file mode 100644
index 0000000000..918ae54f55
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep7.argument-1-Arg.module-type-T.index.html
@@ -0,0 +1,42 @@
+
+
+ T (test.Ocamlary.Dep7.1-Arg.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep7 »
+ 1-Arg » T
+
+
+
+
+
+
+
+ module
+ type
+ R
+ = S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep7.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep7.index.html
new file mode 100644
index 0000000000..c14a7a77ca
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep7.index.html
@@ -0,0 +1,50 @@
+
+
+ Dep7 (test.Ocamlary.Dep7)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep7
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ Arg
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
module
+ M
+ : Arg.T
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep8.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep8.index.html
new file mode 100644
index 0000000000..80de4d27ce
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep8.index.html
@@ -0,0 +1,34 @@
+
+
+ Dep8 (test.Ocamlary.Dep8)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep8
+
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep8.module-type-T.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep8.module-type-T.index.html
new file mode 100644
index 0000000000..6d732793aa
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep8.module-type-T.index.html
@@ -0,0 +1,28 @@
+
+
+ T (test.Ocamlary.Dep8.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep8 » T
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep9.argument-1-X.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep9.argument-1-X.index.html
new file mode 100644
index 0000000000..b936d73ae1
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep9.argument-1-X.index.html
@@ -0,0 +1,32 @@
+
+
+ X (test.Ocamlary.Dep9.1-X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Dep9 » 1-X
+
+
+
+
+
+
+
+ module
+ type
+ T
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Dep9.index.html b/test/generators/cases_pre408/html/Ocamlary.Dep9.index.html
new file mode 100644
index 0000000000..21da7e89a1
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Dep9.index.html
@@ -0,0 +1,51 @@
+
+
+ Dep9 (test.Ocamlary.Dep9)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep9
+
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
+ module
+ type
+ T
+ = X.T
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.DoubleInclude1.DoubleInclude2.index.html b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude1.DoubleInclude2.index.html
new file mode 100644
index 0000000000..aef7701e7b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude1.DoubleInclude2.index.html
@@ -0,0 +1,30 @@
+
+
+
+ DoubleInclude2 (test.Ocamlary.DoubleInclude1.DoubleInclude2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ DoubleInclude1 » DoubleInclude2
+
+
+ Module DoubleInclude1.DoubleInclude2
+
+
+
+
+
+
type double_include
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.DoubleInclude1.index.html b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude1.index.html
new file mode 100644
index 0000000000..01a43c59bc
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude1.index.html
@@ -0,0 +1,32 @@
+
+
+ DoubleInclude1 (test.Ocamlary.DoubleInclude1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » DoubleInclude1
+
+
+ Module Ocamlary.DoubleInclude1
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.DoubleInclude3.DoubleInclude2.index.html b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude3.DoubleInclude2.index.html
new file mode 100644
index 0000000000..1a48d56ccc
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude3.DoubleInclude2.index.html
@@ -0,0 +1,30 @@
+
+
+
+ DoubleInclude2 (test.Ocamlary.DoubleInclude3.DoubleInclude2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ DoubleInclude3 » DoubleInclude2
+
+
+ Module DoubleInclude3.DoubleInclude2
+
+
+
+
+
+
type double_include
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.DoubleInclude3.index.html b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude3.index.html
new file mode 100644
index 0000000000..f2e345ea79
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.DoubleInclude3.index.html
@@ -0,0 +1,45 @@
+
+
+ DoubleInclude3 (test.Ocamlary.DoubleInclude3)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » DoubleInclude3
+
+
+ Module Ocamlary.DoubleInclude3
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Empty.index.html b/test/generators/cases_pre408/html/Ocamlary.Empty.index.html
new file mode 100644
index 0000000000..697395583d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Empty.index.html
@@ -0,0 +1,21 @@
+
+
+ Empty (test.Ocamlary.Empty)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Empty
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.ExtMod.index.html b/test/generators/cases_pre408/html/Ocamlary.ExtMod.index.html
new file mode 100644
index 0000000000..42648a742f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.ExtMod.index.html
@@ -0,0 +1,47 @@
+
+
+ ExtMod (test.Ocamlary.ExtMod)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » ExtMod
+
+
+ Module Ocamlary.ExtMod
+
+
+
+
+
+
+ type t +=
+
+
+
+
+
+
+ |
+ Leisureforce
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..35443ea7e5
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,41 @@
+
+
+
+
+ InnerModuleA'
+ (test.Ocamlary.FunctorTypeOf.1-Collection.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ FunctorTypeOf »
+ 1-Collection »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.index.html
new file mode 100644
index 0000000000..d4fb39370c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.index.html
@@ -0,0 +1,69 @@
+
+
+
+ InnerModuleA (test.Ocamlary.FunctorTypeOf.1-Collection.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ FunctorTypeOf »
+ 1-Collection » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..7c79adb942
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+
+ InnerModuleTypeA'
+ (test.Ocamlary.FunctorTypeOf.1-Collection.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ FunctorTypeOf »
+ 1-Collection »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.index.html b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.index.html
new file mode 100644
index 0000000000..7ad18abd07
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.index.html
@@ -0,0 +1,73 @@
+
+
+ Collection (test.Ocamlary.FunctorTypeOf.1-Collection)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ FunctorTypeOf » 1-Collection
+
+
+ Parameter FunctorTypeOf.1-Collection
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..2d7c73bfbf
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.argument-1-Collection.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,40 @@
+
+
+
+
+ InnerModuleTypeA
+ (test.Ocamlary.FunctorTypeOf.1-Collection.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ FunctorTypeOf »
+ 1-Collection » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.index.html b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.index.html
new file mode 100644
index 0000000000..2fef843261
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.FunctorTypeOf.index.html
@@ -0,0 +1,55 @@
+
+
+ FunctorTypeOf (test.Ocamlary.FunctorTypeOf)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » FunctorTypeOf
+
+
+
+
+
+
+
Parameters
+
+
+
Signature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.IncludeInclude1.index.html b/test/generators/cases_pre408/html/Ocamlary.IncludeInclude1.index.html
new file mode 100644
index 0000000000..cd82e4aca6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.IncludeInclude1.index.html
@@ -0,0 +1,38 @@
+
+
+ IncludeInclude1 (test.Ocamlary.IncludeInclude1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » IncludeInclude1
+
+
+ Module Ocamlary.IncludeInclude1
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.index.html b/test/generators/cases_pre408/html/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.index.html
new file mode 100644
index 0000000000..a52f7eaf33
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.index.html
@@ -0,0 +1,31 @@
+
+
+
+ IncludeInclude2 (test.Ocamlary.IncludeInclude1.IncludeInclude2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ IncludeInclude1 » IncludeInclude2
+
+
+ Module type IncludeInclude1.IncludeInclude2
+
+
+
+
+
+
+
type include_include
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.IncludedA.index.html b/test/generators/cases_pre408/html/Ocamlary.IncludedA.index.html
new file mode 100644
index 0000000000..6981fbe812
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.IncludedA.index.html
@@ -0,0 +1,27 @@
+
+
+ IncludedA (test.Ocamlary.IncludedA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » IncludedA
+
+
+ Module Ocamlary.IncludedA
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.M.index.html b/test/generators/cases_pre408/html/Ocamlary.M.index.html
new file mode 100644
index 0000000000..8dabcb550d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.M.index.html
@@ -0,0 +1,27 @@
+
+
+ M (test.Ocamlary.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » M
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.ModuleWithSignature.index.html b/test/generators/cases_pre408/html/Ocamlary.ModuleWithSignature.index.html
new file mode 100644
index 0000000000..e1bf794735
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.ModuleWithSignature.index.html
@@ -0,0 +1,23 @@
+
+
+ ModuleWithSignature (test.Ocamlary.ModuleWithSignature)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » ModuleWithSignature
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.ModuleWithSignatureAlias.index.html b/test/generators/cases_pre408/html/Ocamlary.ModuleWithSignatureAlias.index.html
new file mode 100644
index 0000000000..eb8d393d90
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.ModuleWithSignatureAlias.index.html
@@ -0,0 +1,26 @@
+
+
+
+ ModuleWithSignatureAlias (test.Ocamlary.ModuleWithSignatureAlias)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » ModuleWithSignatureAlias
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.One.index.html b/test/generators/cases_pre408/html/Ocamlary.One.index.html
new file mode 100644
index 0000000000..d7fa457c50
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.One.index.html
@@ -0,0 +1,27 @@
+
+
+ One (test.Ocamlary.One)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » One
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Only_a_module.index.html b/test/generators/cases_pre408/html/Ocamlary.Only_a_module.index.html
new file mode 100644
index 0000000000..c4f6a139fe
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Only_a_module.index.html
@@ -0,0 +1,27 @@
+
+
+ Only_a_module (test.Ocamlary.Only_a_module)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Only_a_module
+
+
+ Module Ocamlary.Only_a_module
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..b4d5fd0991
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+
+ InnerModuleA' (test.Ocamlary.Recollection.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.index.html
new file mode 100644
index 0000000000..f021d98c32
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.index.html
@@ -0,0 +1,67 @@
+
+
+ InnerModuleA (test.Ocamlary.Recollection.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..08d907655f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,38 @@
+
+
+
+
+ InnerModuleTypeA'
+ (test.Ocamlary.Recollection.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..28d23698a7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,40 @@
+
+
+
+
+ InnerModuleA' (test.Ocamlary.Recollection.1-C.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection »
+ 1-C »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.index.html
new file mode 100644
index 0000000000..2d13d0cb7a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.index.html
@@ -0,0 +1,69 @@
+
+
+
+ InnerModuleA (test.Ocamlary.Recollection.1-C.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection »
+ 1-C » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..5036a5dc99
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+
+ InnerModuleTypeA'
+ (test.Ocamlary.Recollection.1-C.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection »
+ 1-C »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.index.html
new file mode 100644
index 0000000000..fc56dd28f6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.index.html
@@ -0,0 +1,73 @@
+
+
+ C (test.Ocamlary.Recollection.1-C)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection » 1-C
+
+
+ Parameter Recollection.1-C
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..565f6a2dcf
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.argument-1-C.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,38 @@
+
+
+
+ InnerModuleTypeA (test.Ocamlary.Recollection.1-C.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection »
+ 1-C » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.index.html
new file mode 100644
index 0000000000..399df13eb7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.index.html
@@ -0,0 +1,100 @@
+
+
+ Recollection (test.Ocamlary.Recollection)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Recollection
+
+
+ Module Ocamlary.Recollection
+
+
+
+
+
+
Parameters
+
+
+
Signature
+
This comment is for CollectionModule
.
+
+
+
+
type collection
+ =
+ C.element
+ list
+
+
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.Recollection.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.Recollection.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..51718cc56a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.Recollection.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,37 @@
+
+
+
+ InnerModuleTypeA (test.Ocamlary.Recollection.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ Recollection » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With10.index.html b/test/generators/cases_pre408/html/Ocamlary.With10.index.html
new file mode 100644
index 0000000000..2c19923738
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With10.index.html
@@ -0,0 +1,39 @@
+
+
+ With10 (test.Ocamlary.With10)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With10
+
+
+ Module Ocamlary.With10
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With10.module-type-T.M.index.html b/test/generators/cases_pre408/html/Ocamlary.With10.module-type-T.M.index.html
new file mode 100644
index 0000000000..99bc713483
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With10.module-type-T.M.index.html
@@ -0,0 +1,32 @@
+
+
+ M (test.Ocamlary.With10.T.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With10 »
+ T » M
+
+
+
+
+
+
+
+ module
+ type
+ S
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With10.module-type-T.index.html b/test/generators/cases_pre408/html/Ocamlary.With10.module-type-T.index.html
new file mode 100644
index 0000000000..277136b49d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With10.module-type-T.index.html
@@ -0,0 +1,42 @@
+
+
+ T (test.Ocamlary.With10.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With10 » T
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With2.index.html b/test/generators/cases_pre408/html/Ocamlary.With2.index.html
new file mode 100644
index 0000000000..a5db9c512b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With2.index.html
@@ -0,0 +1,34 @@
+
+
+ With2 (test.Ocamlary.With2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With2
+
+
+ Module Ocamlary.With2
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With2.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.With2.module-type-S.index.html
new file mode 100644
index 0000000000..95e7348180
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With2.module-type-S.index.html
@@ -0,0 +1,28 @@
+
+
+ S (test.Ocamlary.With2.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With2 » S
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With3.N.index.html b/test/generators/cases_pre408/html/Ocamlary.With3.N.index.html
new file mode 100644
index 0000000000..3bce0710fc
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With3.N.index.html
@@ -0,0 +1,28 @@
+
+
+ N (test.Ocamlary.With3.N)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With3 » N
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With3.index.html b/test/generators/cases_pre408/html/Ocamlary.With3.index.html
new file mode 100644
index 0000000000..e5120f3b6d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With3.index.html
@@ -0,0 +1,38 @@
+
+
+ With3 (test.Ocamlary.With3)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With3
+
+
+ Module Ocamlary.With3
+
+
+
+
+
+
module M
+ = With2
+
+
+
+
+
+
+
module
+ N
+ : M.S
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With4.N.index.html b/test/generators/cases_pre408/html/Ocamlary.With4.N.index.html
new file mode 100644
index 0000000000..58e8e2c71d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With4.N.index.html
@@ -0,0 +1,28 @@
+
+
+ N (test.Ocamlary.With4.N)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With4 » N
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With4.index.html b/test/generators/cases_pre408/html/Ocamlary.With4.index.html
new file mode 100644
index 0000000000..812267dbd8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With4.index.html
@@ -0,0 +1,30 @@
+
+
+ With4 (test.Ocamlary.With4)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With4
+
+
+ Module Ocamlary.With4
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With5.N.index.html b/test/generators/cases_pre408/html/Ocamlary.With5.N.index.html
new file mode 100644
index 0000000000..2a99f5e564
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With5.N.index.html
@@ -0,0 +1,28 @@
+
+
+ N (test.Ocamlary.With5.N)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With5 » N
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With5.index.html b/test/generators/cases_pre408/html/Ocamlary.With5.index.html
new file mode 100644
index 0000000000..8dfd27ff52
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With5.index.html
@@ -0,0 +1,43 @@
+
+
+ With5 (test.Ocamlary.With5)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With5
+
+
+ Module Ocamlary.With5
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With5.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.With5.module-type-S.index.html
new file mode 100644
index 0000000000..2a02825e50
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With5.module-type-S.index.html
@@ -0,0 +1,28 @@
+
+
+ S (test.Ocamlary.With5.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With5 » S
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With6.index.html b/test/generators/cases_pre408/html/Ocamlary.With6.index.html
new file mode 100644
index 0000000000..2333051eaa
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With6.index.html
@@ -0,0 +1,34 @@
+
+
+ With6 (test.Ocamlary.With6)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With6
+
+
+ Module Ocamlary.With6
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With6.module-type-T.M.index.html b/test/generators/cases_pre408/html/Ocamlary.With6.module-type-T.M.index.html
new file mode 100644
index 0000000000..407d31d2ec
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With6.module-type-T.M.index.html
@@ -0,0 +1,40 @@
+
+
+ M (test.Ocamlary.With6.T.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With6 »
+ T » M
+
+
+
+
+
+
+
+ module
+ type
+ S
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With6.module-type-T.index.html b/test/generators/cases_pre408/html/Ocamlary.With6.module-type-T.index.html
new file mode 100644
index 0000000000..beb496331a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With6.module-type-T.index.html
@@ -0,0 +1,33 @@
+
+
+ T (test.Ocamlary.With6.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With6 » T
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With7.argument-1-X.index.html b/test/generators/cases_pre408/html/Ocamlary.With7.argument-1-X.index.html
new file mode 100644
index 0000000000..52815c8124
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With7.argument-1-X.index.html
@@ -0,0 +1,32 @@
+
+
+ X (test.Ocamlary.With7.1-X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With7 » 1-X
+
+
+
+
+
+
+
+ module
+ type
+ T
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With7.index.html b/test/generators/cases_pre408/html/Ocamlary.With7.index.html
new file mode 100644
index 0000000000..edc62f0cfe
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With7.index.html
@@ -0,0 +1,51 @@
+
+
+ With7 (test.Ocamlary.With7)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With7
+
+
+ Module Ocamlary.With7
+
+
+
+
+
+
Parameters
+
+
+
+
+
module
+ X
+ : sig ...
+ end
+
+
+
+
+
Signature
+
+
+
+
+ module
+ type
+ T
+ = X.T
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With9.index.html b/test/generators/cases_pre408/html/Ocamlary.With9.index.html
new file mode 100644
index 0000000000..a1b4d9f294
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With9.index.html
@@ -0,0 +1,34 @@
+
+
+ With9 (test.Ocamlary.With9)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With9
+
+
+ Module Ocamlary.With9
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.With9.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.With9.module-type-S.index.html
new file mode 100644
index 0000000000..635624dc1e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.With9.module-type-S.index.html
@@ -0,0 +1,28 @@
+
+
+ S (test.Ocamlary.With9.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With9 » S
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.class-empty_class.index.html b/test/generators/cases_pre408/html/Ocamlary.class-empty_class.index.html
new file mode 100644
index 0000000000..caa4504e5a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.class-empty_class.index.html
@@ -0,0 +1,19 @@
+
+
+ empty_class (test.Ocamlary.empty_class)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » empty_class
+
+
+ Class Ocamlary.empty_class
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.class-one_method_class.index.html b/test/generators/cases_pre408/html/Ocamlary.class-one_method_class.index.html
new file mode 100644
index 0000000000..1de4787279
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.class-one_method_class.index.html
@@ -0,0 +1,27 @@
+
+
+ one_method_class (test.Ocamlary.one_method_class)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » one_method_class
+
+
+ Class Ocamlary.one_method_class
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.class-param_class.index.html b/test/generators/cases_pre408/html/Ocamlary.class-param_class.index.html
new file mode 100644
index 0000000000..9be3fcb54a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.class-param_class.index.html
@@ -0,0 +1,31 @@
+
+
+ param_class (test.Ocamlary.param_class)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » param_class
+
+
+ Class Ocamlary.param_class
+
+
+
+
+
+
+ method v :
+ 'a
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.class-two_method_class.index.html b/test/generators/cases_pre408/html/Ocamlary.class-two_method_class.index.html
new file mode 100644
index 0000000000..30c873a8ef
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.class-two_method_class.index.html
@@ -0,0 +1,38 @@
+
+
+ two_method_class (test.Ocamlary.two_method_class)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » two_method_class
+
+
+ Class Ocamlary.two_method_class
+
+
+
+
+
+
+
method undo : unit
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.index.html b/test/generators/cases_pre408/html/Ocamlary.index.html
new file mode 100644
index 0000000000..4ff7f6aad4
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.index.html
@@ -0,0 +1,2923 @@
+
+
+ Ocamlary (test.Ocamlary)
+
+
+
+
+
+
+
+ Up –
+ test » Ocamlary
+
+
+ Module Ocamlary
+ This is an interface with all of the
+ module system features. This documentation demonstrates:
+
+ A numbered list:
3 2 1
+ David Sheets is the author.
+
+
+
+
+
+
+
You may find more information about this HTML documentation renderer
+ at
+ github.com/dsheets/ocamlary
+ .
+
This is some verbatim text:
verbatim
+
This is some verbatim text:
[][df[]]}}
+
Here is some raw LaTeX:
+
Here is an index table of Empty
modules:
+
+ Empty
+ A plain, empty module
+
+ EmptyAlias
+ A plain module alias of Empty
+
+ Here is a table of links to indexes: indexlist
+
Here is some superscript: x2
+
Here is some subscript: x0
+
Here are some escaped brackets: { [ @ ] }
+
Here is some emphasis followed by code
.
+
An unassociated comment
+
Level 1
+
Level 2
+
Level 3
+
Level 4
+
+ Basic module stuff
+
+
+
+
+
module
+ Empty
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ Empty
+ = sig ...
+ end
+
+
+
+
An ambiguous, misnamed module type
+
+
+
+
An ambiguous, misnamed module type
+
Section 9000
+
+
+
+
module
+ EmptyAlias
+ = Empty
+
+
+
A plain module alias of Empty
+
+
+
EmptySig
+
+
+
+
+ module
+ type
+
+ EmptySig
+ = sig ...
+ end
+
+
+
A plain, empty module signature
+
+
+
+
A plain, empty module signature alias of
+
+
+
+
+
+
A plain module of a signature of
+ EmptySig
+ (reference)
+
+
+
+
+
+
A plain module with an alias signature
+
+
+
+
+
module
+ One
+ : sig ...
+ end
+
+
+
+
+
+
+
+
There's a signature in a module in this signature.
+
+
+
+
+
+
+ module
+ type
+
+ SuperSig
+ = sig ...
+ end
+
+
+
+
+
For a good time, see SuperSig
.SubSigA.subSig or
+ SuperSig
.SubSigB.subSig or
+
+ SuperSig.EmptySig
+ . Section Section 9000 is also interesting.
+ EmptySig is the section and
+ EmptySig
+ is the module signature.
+
+
+
+
+
module
+ Buffer
+ : sig ...
+ end
+
+
+
+
Some text before exception title.
+
+ Basic exception
+ stuff
+ After exception title.
+
+
+
+
exception
+ Kaboom
+ of unit
+
+
+
Unary exception constructor
+
+
+
+
+
exception
+ Kablam
+ of unit * unit
+
+
+
Binary exception constructor
+
+
+
+
+
exception
+ Kapow
+ of unit * unit
+
+
+
+
+
Unary exception constructor over binary tuple
+
+
+
+
+
+
exception
+ EmptySig
+
+
+
+
+
+
+
+
exception
+ EmptySigAlias
+
+
+
+
+
+
+
+
+
+ type
+ ('a, 'b) a_function
+
+ =
+ 'a
+ ->
+ 'b
+
+
+
+
+
+
+
+
+
+ val a_function :
+ x:int -> int
+
+
+
+
+
This is a_function
with param and return type.
+
+
+
+
+
+
+
+
+
+ val fun_maybe :
+ ?yes:unit ->
+ unit -> int
+
+
+
+
+
+
+
+
+ val not_found :
+ unit -> unit
+
+
+
+
+
+
+
+
+
val ocaml_org : string
+
+
+
+
+
+
+
+
val some_file : string
+
+
+
+
+
+
+
+
val some_doc : string
+
+
+
+
+
+
+
+
+ val since_mesozoic : unit
+
+
+
+
This value was introduced in the Mesozoic era.
+
+
+
+
+
+
+
val changing : unit
+
+
+
+
This value has had changes in 1.0.0, 1.1.0, and 1.2.0.
+
+
+
+
+
+
+ Some Operators
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+ Advanced Module
+ Stuff
+
+
+
+
+
This comment is for CollectionModule
.
+
+
+
+
+
+
+
+
+ module
+ type
+ MMM
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+
+
+ module
+ type
+ A
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ B
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ C
+ = sig ...
+ end
+
+
+
+
This module type includes two signatures.
+
+
+
+
+
+
This comment is for FunctorTypeOf
.
+
+
+
+
+
+
This comment is for IncludeModuleType
.
+
+
+
+
+
+
+ module
+ type
+
+ ToInclude
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ include
+ ToInclude
+
+
+
+
+
+
+
module
+ IncludedA
+ : sig ...
+ end
+
+
+
+
+
+
+
+ module
+ type
+
+ IncludedB
+ = sig ...
+ end
+
+
+
+
+
+
+
+ Advanced Type Stuff
+
+
+
+
+
type record
+ = {
+
+
+
+
+
+ field1 : int;
+
+
+ This comment is for field1
.
+
+
+
+
+
+
+ field2 : int;
+
+
+ This comment is for field2
.
+
+
+
+
}
+
+
This comment is for record
.
+
This comment is also for record
.
+
+
+
+
+
+
type mutable_record
+ = {
+
+
+
+
+
+ mutable a : int;
+
+
+
+ a
is first and mutable
+
+
+
+
+
+
+ b : unit;
+
+
+ b
is second and immutable
+
+
+
+
+
+
+ mutable c : int;
+
+
+
+ c
is third and mutable
+
+
+
+
}
+
+
+
+
+
+
type universe_record
+ = {
+
+
+
+
+
+
+ nihilate : a.
+ 'a
+ ->
+ unit;
+
+
+
+
+
}
+
+
+
+
+
+
type variant
+ =
+
+
+
+
+
+ |
+ TagA
+
+
+
+ This comment is for TagA
.
+
+
+
+
+
+
+ |
+ ConstrB
+ of int
+
+
+
+
+ This comment is for ConstrB
.
+
+
+
+
+
+
+ |
+ ConstrC
+ of int * int
+
+
+
+
+ This comment is for binary ConstrC
.
+
+
+
+
+
+
+ |
+ ConstrD
+ of int * int
+
+
+
+
+ This comment is for unary ConstrD
of binary tuple.
+
+
+
+
+
+
This comment is for variant
.
+
This comment is also for variant
.
+
+
+
+
+
+
type poly_variant
+ = [
+
+
+
+
+
+ |
`TagA
+
+
+
+
+
+ |
+ `ConstrB of int
+
+
+
+
]
+
+
+
This comment is for poly_variant
.
+
Wow! It was a polymorphic variant!
+
+
+
+
+
+
+ type (_, _) full_gadt
+ =
+
+
+
+
+
+ |
+ Tag :
+ (unit, unit)
+ full_gadt
+
+
+
+
+
+
+
+
+ |
+ First :
+ 'a
+ ->
+ ('a , unit)
+ full_gadt
+
+
+
+
+
+
+
+
+ |
+ Second :
+ 'a
+ ->
+ (unit, 'a )
+ full_gadt
+
+
+
+
+
+
+
+
+ |
+ Exist :
+ 'a * 'b
+ ->
+ ('b , unit)
+ full_gadt
+
+
+
+
+
+
+
+
This comment is for full_gadt
.
+
Wow! It was a GADT!
+
+
+
+
+
+
+ type 'a partial_gadt
+ =
+
+
+
+
+
+ |
+ AscribeTag :
+ 'a
+ partial_gadt
+
+
+
+
+
+
+
+
+ |
+ OfTag
+ of
+ 'a
+ partial_gadt
+
+
+
+
+
+
+
+
+ |
+ ExistGadtTag :
+ (
+ 'a
+ ->
+ 'b )
+ ->
+ 'a
+ partial_gadt
+
+
+
+
+
+
+
+
+
This comment is for partial_gadt
.
+
Wow! It was a mixed GADT!
+
+
+
+
+
This comment is for alias
.
+
+
+
+
+
This comment is for tuple
.
+
+
+
+
+
+
type variant_alias
+ = variant =
+
+
+
+
+
+ |
+ TagA
+
+
+
+
+
+
+ |
+ ConstrB
+ of int
+
+
+
+
+
+
+
+ |
+ ConstrC
+ of int * int
+
+
+
+
+
+
+
+ |
+ ConstrD
+ of int * int
+
+
+
+
+
+
+
+
This comment is for variant_alias
.
+
+
+
+
+
+
type record_alias
+ = record =
+ {
+
+
+
+
+
+ field1 : int;
+
+
+
+
+
+ field2 : int;
+
+
+
}
+
+
+
This comment is for record_alias
.
+
+
+
+
+
+
type poly_variant_union
+ = [
+
+
]
+
+
+
This comment is for poly_variant_union
.
+
+
+
+
+
+
+ type
+ 'a poly_poly_variant
+ = [
+
+
+
+
+
+ |
+
+ `TagA of
+ 'a
+
+
+
+
+
]
+
+
+
+
+
+
+ type
+ ('a, 'b) bin_poly_poly_variant
+ = [
+
+
+
+
+
+ |
+
+ `TagA of
+ 'a
+
+
+
+
+
+
+
+ |
+
+ `ConstrB of
+ 'b
+
+
+
+
+
]
+
+
+
+
+
+
+ type
+ 'a open_poly_variant
+
+ = [> `TagA ] as 'a
+
+
+
+
+
+
+
+
+ type
+ 'a open_poly_variant2
+
+ = [> `ConstrB of int ]
+ as 'a
+
+
+
+
+
+
+
+
+
+ type 'a poly_fun
+ =
+ [> `ConstrB of int ]
+ as 'a
+ ->
+ 'a
+
+
+
+
+
+
+
+
+ type
+ 'a poly_fun_constraint
+
+ =
+ 'a
+ ->
+ 'a
+
+ constraint
+ 'a = [> `TagA ]
+
+
+
+
+
+
+
+
+ type
+ 'a closed_poly_variant
+
+ = [< `One | `Two ]
+ as 'a
+
+
+
+
+
+
+
+
+ type
+ 'a clopen_poly_variant
+
+ =
+ [< `One | `Two of int
+ | `Three Two Three ]
+ as 'a
+
+
+
+
+
+
+
+
type nested_poly_variant
+ = [
+
+
+
+
+
+ |
`A
+
+
+
+
+
+ |
+
+ `B of
+ [ `B1 | `B2 ]
+
+
+
+
+
+
+
+ |
`C
+
+
+
+
+
+ |
+
+ `D of
+ [ `D1 of [ `D1a ] ]
+
+
+
+
+
]
+
+
+
+
+
+
+ type
+ ('a, 'b) full_gadt_alias
+
+ =
+
+ ('a ,
+ 'b )
+ full_gadt
+
+ =
+
+
+
+
+
This comment is for full_gadt_alias
.
+
+
+
+
+
+
+ type
+ 'a partial_gadt_alias
+
+ =
+ 'a
+ partial_gadt
+
+ =
+
+
+
+
+
This comment is for partial_gadt_alias
.
+
+
+
+
+
+
exception
+ Exn_arrow : unit
+ -> exn
+
+
+
+
+
+
+
+
+
type mutual_constr_a
+ =
+
+
+
+
+
+
+
+
+
and mutual_constr_b
+ =
+
+
+
+
+
+ | B
+
+
+
+
+
+
+ |
+ A_ish
+ of
+ mutual_constr_a
+
+
+
+
+ This comment must be here for the next to associate correctly.
+
+
+
+
+
+
+
+
+
+
+
type rec_obj
+ =
+ < f : int; g :
+ unit -> unit;
+ h : rec_obj ; >
+
+
+
+
+
+
+
+
+
+ type 'a open_obj
+ =
+ < f : int; g :
+ unit -> unit;
+ .. >
+ as 'a
+
+
+
+
+
+
+
+
type 'a oof
+ =
+ < a : unit; .. >
+ as 'a
+ ->
+ 'a
+
+
+
+
+
+
+
+
+ type 'a any_obj
+ = < .. > as 'a
+
+
+
+
+
+
+
+
type empty_obj
+ = < >
+
+
+
+
+
+
+
type one_meth
+ = < meth : unit; >
+
+
+
+
+
A mystery wrapped in an ellipsis
+
+
+
+
+
+
+ type ext +=
+
+
+
+
+
+
+ |
+ ExtC
+ of unit
+
+
+
+
+
+
+
+ |
+ ExtD
+ of ext
+
+
+
+
+
+
+
+
+
+
+
+
+
+ type 'a poly_ext
+ = ..
+
+
+
+
+
+
+ type
+ poly_ext +=
+
+
+
+
+
+ |
+ Foo
+ of 'b
+
+
+
+
+
+
+ |
+ Bar
+ of 'b
+ * 'b
+
+
+
+
+ 'b poly_ext
+
+
+
+
+
+
+
+
+ type
+ poly_ext +=
+
+
+
+
+
+
+ |
+ Quux
+ of 'c
+
+
+
+
+ 'c poly_ext
+
+
+
+
+
+
+
+
+
module
+ ExtMod
+ : sig ...
+ end
+
+
+
+
+
+
+
+ type
+ ExtMod.t +=
+
+
+
+
+
+
+ |
+ ZzzTop0
+
+
+
+ It's got the rock
+
+
+
+
+
+
+
+
+ type
+ ExtMod.t +=
+
+
+
+
+
+
+ |
+ ZzzTop
+ of unit
+
+
+
+
+ and it packs a unit.
+
+
+
+
+
+
+
+
+ val launch_missiles :
+ unit -> unit
+
+
+
Rotate keys on my mark...
+
+
+
+
+
type my_mod
+ =
+ (module
+ COLLECTION )
+
+
+
+
+
A brown paper package tied up with string
+
+
+
+
+
+
+
+
+
class 'a
+ param_class
+ :
+ 'a
+ ->
+ object ...
+ end
+
+
+
+
+
+
+
+
+
+ type 'a my_unit_class
+
+ =
+ unit param_class
+ as 'a
+
+
+
+
+
+
+
+
module
+ Dep1
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Dep2
+ (Arg :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
+
module
+ Dep3
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Dep4
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Dep5
+ (Arg :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
+
+
module
+ Dep6
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Dep7
+ (Arg :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
+
module
+ Dep8
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Dep9
+ (X :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
+
module
+ Dep11
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ Dep12
+ (Arg :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
+
+
+ module
+ type
+ With1
+ = sig ...
+ end
+
+
+
+
+
+
+
+
module
+ With2
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
+
+
+
module
+ With5
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ With6
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ With7
+ (X :
+ sig ... end
+ ) : sig ...
+ end
+
+
+
+
+
+
+
+
+
module
+ With9
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ With10
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+ include
+ IncludeInclude2
+
+
+
+
+
+
+
type include_include
+
+
+
+
+
+
Trying
+ the {!modules: ...} command.
+
+
With ocamldoc, toplevel units will be linked and documented, while
+ submodules will behave as simple references.
+
+
With odoc, everything should be resolved (and linked) but only
+ toplevel units will be documented.
+
+
+
+
+ Weirder usages involving module types
+
+
IncludeInclude1
.IncludeInclude2
+ Dep4
.T
+ A.Q
+
+
+ Playing
+ with @canonical paths
+
+
+
+
Aliases again
+
+
+
+
module
+ Aliases
+ : sig ...
+ end
+
+
+
Let's imitate jst's layout.
+
+
+ Section title
+ splicing
+ I can refer to
+
But also to things in submodules:
+
+ {!section:SuperSig.SubSigA.subSig}
:
+ SuperSig
.SubSigA.subSig
+
+ {!Aliases.incl}
:
+ Aliases:incl
+
+ And just to make sure we do not mess up:
+
+ {{!section:indexmodules}A}
:
+ A
+ {{!aliases}B}
: B
+ {{!section:SuperSig.SubSigA.subSig}C}
:
+ C
+
+ {{!Aliases.incl}D}
:
+ D
+
+
+
+ New reference
+ syntax
+
+
+
+
+
+ module
+ type
+ M
+ = sig ...
+ end
+
+
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
Here goes:
+
+ {!module-M.t}
:
+ M.t
+
+ {!module-type-M.t}
:
+ M.t
+
+
+
Some here should fail:
+
+
+
+
+
+ module
+ type
+
+ TypeExt
+ = sig ...
+ end
+
+
+
+
+
+
+
+
type new_t
+ = ..
+
+
+
+
+
+
+ type new_t
+ +=
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..2335eed72c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+ InnerModuleA' (test.Ocamlary.A.Q.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ A »
+ Q »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.index.html
new file mode 100644
index 0000000000..f8c3c1b865
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.index.html
@@ -0,0 +1,68 @@
+
+
+ InnerModuleA (test.Ocamlary.A.Q.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ A » Q
+ » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..1d55af581b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,37 @@
+
+
+
+ InnerModuleTypeA' (test.Ocamlary.A.Q.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ A »
+ Q »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.index.html
new file mode 100644
index 0000000000..18e4e24be2
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.index.html
@@ -0,0 +1,72 @@
+
+
+ Q (test.Ocamlary.A.Q)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ A » Q
+
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..635db4ac95
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-A.Q.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,37 @@
+
+
+ InnerModuleTypeA (test.Ocamlary.A.Q.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ A » Q
+ » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-A.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-A.index.html
new file mode 100644
index 0000000000..648ad5cf73
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-A.index.html
@@ -0,0 +1,37 @@
+
+
+ A (test.Ocamlary.A)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » A
+
+
+ Module type Ocamlary.A
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..1b9f7493fd
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+ InnerModuleA' (test.Ocamlary.B.Q.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ B »
+ Q »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.index.html
new file mode 100644
index 0000000000..33e679dd57
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.index.html
@@ -0,0 +1,68 @@
+
+
+ InnerModuleA (test.Ocamlary.B.Q.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ B » Q
+ » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..c94e9480ce
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,37 @@
+
+
+
+ InnerModuleTypeA' (test.Ocamlary.B.Q.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ B »
+ Q »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.index.html
new file mode 100644
index 0000000000..c7a2d42a5b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.index.html
@@ -0,0 +1,72 @@
+
+
+ Q (test.Ocamlary.B.Q)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ B » Q
+
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..63047d7b61
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-B.Q.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,37 @@
+
+
+ InnerModuleTypeA (test.Ocamlary.B.Q.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ B » Q
+ » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-B.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-B.index.html
new file mode 100644
index 0000000000..bc7edfea1c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-B.index.html
@@ -0,0 +1,37 @@
+
+
+ B (test.Ocamlary.B)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » B
+
+
+ Module type Ocamlary.B
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..0bc342bc00
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+ InnerModuleA' (test.Ocamlary.C.Q.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ C »
+ Q »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.index.html
new file mode 100644
index 0000000000..9369a59fe2
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.index.html
@@ -0,0 +1,68 @@
+
+
+ InnerModuleA (test.Ocamlary.C.Q.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ C » Q
+ » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..17ae73d190
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,37 @@
+
+
+
+ InnerModuleTypeA' (test.Ocamlary.C.Q.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ C »
+ Q »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.index.html
new file mode 100644
index 0000000000..72698b6f84
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.index.html
@@ -0,0 +1,72 @@
+
+
+ Q (test.Ocamlary.C.Q)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ C » Q
+
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..07f16b5735
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-C.Q.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,37 @@
+
+
+ InnerModuleTypeA (test.Ocamlary.C.Q.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ C » Q
+ » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-C.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-C.index.html
new file mode 100644
index 0000000000..df8c991352
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-C.index.html
@@ -0,0 +1,77 @@
+
+
+ C (test.Ocamlary.C)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » C
+
+
+
+
+
+
+
+ include
+ A
+
+
+
+
+
+
+
+
+
+
+
+ include
+ B
+ with
+ type
+ t :=
+ t
+ and
+ module
+ Q :=
+ Q
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..14826adf55
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,38 @@
+
+
+
+ InnerModuleA' (test.Ocamlary.COLLECTION.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ COLLECTION »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.index.html
new file mode 100644
index 0000000000..f80dd2ed80
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.index.html
@@ -0,0 +1,67 @@
+
+
+ InnerModuleA (test.Ocamlary.COLLECTION.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ COLLECTION » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..280c8622cf
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,38 @@
+
+
+
+
+ InnerModuleTypeA'
+ (test.Ocamlary.COLLECTION.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ COLLECTION »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.index.html
new file mode 100644
index 0000000000..c9b689f205
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.index.html
@@ -0,0 +1,73 @@
+
+
+ COLLECTION (test.Ocamlary.COLLECTION)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » COLLECTION
+
+
+ Module type Ocamlary.COLLECTION
+ module type of
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..501307b2c0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-COLLECTION.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,37 @@
+
+
+
+ InnerModuleTypeA (test.Ocamlary.COLLECTION.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ COLLECTION » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-Dep10.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-Dep10.index.html
new file mode 100644
index 0000000000..c8022d82be
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-Dep10.index.html
@@ -0,0 +1,29 @@
+
+
+ Dep10 (test.Ocamlary.Dep10)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Dep10
+
+
+ Module type Ocamlary.Dep10
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-Empty.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-Empty.index.html
new file mode 100644
index 0000000000..a15251b7d6
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-Empty.index.html
@@ -0,0 +1,28 @@
+
+
+ Empty (test.Ocamlary.Empty)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » Empty
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-EmptySig.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-EmptySig.index.html
new file mode 100644
index 0000000000..ed14fde314
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-EmptySig.index.html
@@ -0,0 +1,20 @@
+
+
+ EmptySig (test.Ocamlary.EmptySig)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » EmptySig
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-EmptySigAlias.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-EmptySigAlias.index.html
new file mode 100644
index 0000000000..9705c27e9a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-EmptySigAlias.index.html
@@ -0,0 +1,21 @@
+
+
+ EmptySigAlias (test.Ocamlary.EmptySigAlias)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » EmptySigAlias
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-IncludeInclude2.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-IncludeInclude2.index.html
new file mode 100644
index 0000000000..870add67a2
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-IncludeInclude2.index.html
@@ -0,0 +1,28 @@
+
+
+ IncludeInclude2 (test.Ocamlary.IncludeInclude2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » IncludeInclude2
+
+
+ Module type Ocamlary.IncludeInclude2
+
+
+
+
+
+
type include_include
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-IncludeModuleType.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-IncludeModuleType.index.html
new file mode 100644
index 0000000000..cfeb08cb79
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-IncludeModuleType.index.html
@@ -0,0 +1,36 @@
+
+
+ IncludeModuleType (test.Ocamlary.IncludeModuleType)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » IncludeModuleType
+
+
+
+
+
+
This comment is for include EmptySigAlias
.
+
+
+
+
+ include
+ EmptySigAlias
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-IncludedB.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-IncludedB.index.html
new file mode 100644
index 0000000000..625e08ff1f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-IncludedB.index.html
@@ -0,0 +1,27 @@
+
+
+ IncludedB (test.Ocamlary.IncludedB)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » IncludedB
+
+
+ Module type Ocamlary.IncludedB
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-M.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-M.index.html
new file mode 100644
index 0000000000..45d7daf044
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-M.index.html
@@ -0,0 +1,27 @@
+
+
+ M (test.Ocamlary.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » M
+
+
+ Module type Ocamlary.M
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..ae5fed7de3
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,39 @@
+
+
+
+ InnerModuleA' (test.Ocamlary.MMM.C.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ MMM »
+ C »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.index.html
new file mode 100644
index 0000000000..1a3ea52cb1
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.index.html
@@ -0,0 +1,68 @@
+
+
+ InnerModuleA (test.Ocamlary.MMM.C.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ MMM » C
+ » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..fbc36a7998
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,38 @@
+
+
+
+
+ InnerModuleTypeA' (test.Ocamlary.MMM.C.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ MMM »
+ C »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.index.html
new file mode 100644
index 0000000000..19a21b645b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.index.html
@@ -0,0 +1,73 @@
+
+
+ C (test.Ocamlary.MMM.C)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ MMM » C
+
+
+
+
This comment is for CollectionModule
.
+
+
+
This comment is for collection
.
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..f73ec0cb81
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.C.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,37 @@
+
+
+ InnerModuleTypeA (test.Ocamlary.MMM.C.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ MMM » C
+ » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.index.html
new file mode 100644
index 0000000000..d755f5e185
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MMM.index.html
@@ -0,0 +1,31 @@
+
+
+ MMM (test.Ocamlary.MMM)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » MMM
+
+
+ Module type Ocamlary.MMM
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-MissingComment.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-MissingComment.index.html
new file mode 100644
index 0000000000..df55a0d68b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-MissingComment.index.html
@@ -0,0 +1,28 @@
+
+
+ MissingComment (test.Ocamlary.MissingComment)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » MissingComment
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude1.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude1.index.html
new file mode 100644
index 0000000000..4e887412be
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude1.index.html
@@ -0,0 +1,38 @@
+
+
+ NestedInclude1 (test.Ocamlary.NestedInclude1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » NestedInclude1
+
+
+ Module type Ocamlary.NestedInclude1
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.index.html
new file mode 100644
index 0000000000..4b387c2fb3
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.index.html
@@ -0,0 +1,31 @@
+
+
+
+ NestedInclude2 (test.Ocamlary.NestedInclude1.NestedInclude2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ NestedInclude1 » NestedInclude2
+
+
+ Module type NestedInclude1.NestedInclude2
+
+
+
+
+
+
+
type nested_include
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude2.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude2.index.html
new file mode 100644
index 0000000000..26029f45d0
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-NestedInclude2.index.html
@@ -0,0 +1,28 @@
+
+
+ NestedInclude2 (test.Ocamlary.NestedInclude2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » NestedInclude2
+
+
+ Module type Ocamlary.NestedInclude2
+
+
+
+
+
+
type nested_include
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-RECOLLECTION.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-RECOLLECTION.index.html
new file mode 100644
index 0000000000..f316a8a5f4
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-RECOLLECTION.index.html
@@ -0,0 +1,32 @@
+
+
+ RECOLLECTION (test.Ocamlary.RECOLLECTION)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » RECOLLECTION
+
+
+ Module type Ocamlary.RECOLLECTION
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.index.html
new file mode 100644
index 0000000000..8776c33632
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.index.html
@@ -0,0 +1,40 @@
+
+
+
+
+ InnerModuleA'
+ (test.Ocamlary.RecollectionModule.InnerModuleA.InnerModuleA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ RecollectionModule »
+ InnerModuleA » InnerModuleA'
+
+
+
+
+
+
+
type t
+ =
+ (unit, unit)
+ a_function
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.index.html
new file mode 100644
index 0000000000..ee1b52e57d
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.index.html
@@ -0,0 +1,68 @@
+
+
+
+ InnerModuleA (test.Ocamlary.RecollectionModule.InnerModuleA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ RecollectionModule » InnerModuleA
+
+
+
+
+
+
+
+
This comment is for InnerModuleA'
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA'
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html
new file mode 100644
index 0000000000..d975ffa732
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html
@@ -0,0 +1,38 @@
+
+
+
+
+ InnerModuleTypeA'
+ (test.Ocamlary.RecollectionModule.InnerModuleA.InnerModuleTypeA')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ RecollectionModule »
+ InnerModuleA » InnerModuleTypeA'
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.index.html
new file mode 100644
index 0000000000..c329decb32
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.index.html
@@ -0,0 +1,83 @@
+
+
+ RecollectionModule (test.Ocamlary.RecollectionModule)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » RecollectionModule
+
+
+ Module type Ocamlary.RecollectionModule
+
+
+
+
+
+
+
+
This comment is for InnerModuleA
.
+
+
+
+
+
+
This comment is for InnerModuleTypeA
.
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.module-type-InnerModuleTypeA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.module-type-InnerModuleTypeA.index.html
new file mode 100644
index 0000000000..e568e31530
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-RecollectionModule.module-type-InnerModuleTypeA.index.html
@@ -0,0 +1,38 @@
+
+
+
+ InnerModuleTypeA (test.Ocamlary.RecollectionModule.InnerModuleTypeA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ RecollectionModule » InnerModuleTypeA
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.Inner.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.Inner.index.html
new file mode 100644
index 0000000000..5ea76c1b4e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.Inner.index.html
@@ -0,0 +1,35 @@
+
+
+ Inner (test.Ocamlary.SigForMod.Inner)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SigForMod » Inner
+
+
+ Module SigForMod.Inner
+
+
+
+
+
+
+ module
+ type
+ Empty
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.index.html
new file mode 100644
index 0000000000..40192eeb85
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.index.html
@@ -0,0 +1,21 @@
+
+
+ Empty (test.Ocamlary.SigForMod.Inner.Empty)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SigForMod »
+ Inner » Empty
+
+
+ Module type Inner.Empty
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.index.html
new file mode 100644
index 0000000000..61a001228a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SigForMod.index.html
@@ -0,0 +1,33 @@
+
+
+ SigForMod (test.Ocamlary.SigForMod)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » SigForMod
+
+
+
+
+
+
+
module
+ Inner
+ : sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.index.html
new file mode 100644
index 0000000000..7089e368d2
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.index.html
@@ -0,0 +1,90 @@
+
+
+ SuperSig (test.Ocamlary.SuperSig)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » SuperSig
+
+
+ Module type Ocamlary.SuperSig
+
+
+
+
+
+
+ module
+ type
+
+ SubSigA
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+
+ SubSigB
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+
+ EmptySig
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+ One
+ = sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+
+ SuperSig
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-EmptySig.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-EmptySig.index.html
new file mode 100644
index 0000000000..56852abfd2
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-EmptySig.index.html
@@ -0,0 +1,29 @@
+
+
+ EmptySig (test.Ocamlary.SuperSig.EmptySig)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SuperSig » EmptySig
+
+
+ Module type SuperSig.EmptySig
+
+
+
+
+
+
type not_actually_empty
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-One.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-One.index.html
new file mode 100644
index 0000000000..a0f542e129
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-One.index.html
@@ -0,0 +1,28 @@
+
+
+ One (test.Ocamlary.SuperSig.One)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SuperSig » One
+
+
+ Module type SuperSig.One
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.index.html
new file mode 100644
index 0000000000..2e161b4227
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.index.html
@@ -0,0 +1,30 @@
+
+
+ SubSigAMod (test.Ocamlary.SuperSig.SubSigA.SubSigAMod)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SuperSig »
+ SubSigA » SubSigAMod
+
+
+ Module SubSigA.SubSigAMod
+
+
+
+
+
+
type sub_sig_a_mod
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigA.index.html
new file mode 100644
index 0000000000..8b4fc41135
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigA.index.html
@@ -0,0 +1,48 @@
+
+
+ SubSigA (test.Ocamlary.SuperSig.SubSigA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SuperSig » SubSigA
+
+
+ Module type SuperSig.SubSigA
+
+
+
+
+
+
A Labeled Section
+ Header Inside of a Signature
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigB.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigB.index.html
new file mode 100644
index 0000000000..31b8b14463
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SubSigB.index.html
@@ -0,0 +1,39 @@
+
+
+ SubSigB (test.Ocamlary.SuperSig.SubSigB)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SuperSig » SubSigB
+
+
+ Module type SuperSig.SubSigB
+
+
+
+
+
+
Another Labeled
+ Section Header Inside of a Signature
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SuperSig.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SuperSig.index.html
new file mode 100644
index 0000000000..0ba444d17f
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-SuperSig.module-type-SuperSig.index.html
@@ -0,0 +1,20 @@
+
+
+ SuperSig (test.Ocamlary.SuperSig.SuperSig)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ SuperSig » SuperSig
+
+
+ Module type SuperSig.SuperSig
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.IncludedA.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.IncludedA.index.html
new file mode 100644
index 0000000000..16e5bb6c9a
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.IncludedA.index.html
@@ -0,0 +1,28 @@
+
+
+ IncludedA (test.Ocamlary.ToInclude.IncludedA)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ ToInclude » IncludedA
+
+
+ Module ToInclude.IncludedA
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.index.html
new file mode 100644
index 0000000000..c7c893faf2
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.index.html
@@ -0,0 +1,46 @@
+
+
+ ToInclude (test.Ocamlary.ToInclude)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » ToInclude
+
+
+ Module type Ocamlary.ToInclude
+
+
+
+
+
+
module
+ IncludedA
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+ module
+ type
+
+ IncludedB
+ = sig ...
+ end
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.module-type-IncludedB.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.module-type-IncludedB.index.html
new file mode 100644
index 0000000000..0c5230e769
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-ToInclude.module-type-IncludedB.index.html
@@ -0,0 +1,28 @@
+
+
+ IncludedB (test.Ocamlary.ToInclude.IncludedB)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ ToInclude » IncludedB
+
+
+ Module type ToInclude.IncludedB
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-TypeExt.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-TypeExt.index.html
new file mode 100644
index 0000000000..dee925b414
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-TypeExt.index.html
@@ -0,0 +1,56 @@
+
+
+ TypeExt (test.Ocamlary.TypeExt)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » TypeExt
+
+
+ Module type Ocamlary.TypeExt
+
+
+
+
+
+
+
+
+ val f :
+ t ->
+ unit
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-TypeExtPruned.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-TypeExtPruned.index.html
new file mode 100644
index 0000000000..2785e188cb
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-TypeExtPruned.index.html
@@ -0,0 +1,50 @@
+
+
+ TypeExtPruned (test.Ocamlary.TypeExtPruned)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » TypeExtPruned
+
+
+ Module type Ocamlary.TypeExtPruned
+
+
+
+
+
+ type
+ new_t +=
+
+
+
+
+
+
+
+
+
+ val f :
+ new_t
+ ->
+ unit
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With1.M.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With1.M.index.html
new file mode 100644
index 0000000000..aaa0474696
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With1.M.index.html
@@ -0,0 +1,32 @@
+
+
+ M (test.Ocamlary.With1.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With1 » M
+
+
+
+
+
+
+
+ module
+ type
+ S
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With1.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With1.index.html
new file mode 100644
index 0000000000..994d998f92
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With1.index.html
@@ -0,0 +1,40 @@
+
+
+ With1 (test.Ocamlary.With1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With1
+
+
+ Module type Ocamlary.With1
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With11.N.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With11.N.index.html
new file mode 100644
index 0000000000..1f18ad98e8
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With11.N.index.html
@@ -0,0 +1,30 @@
+
+
+ N (test.Ocamlary.With11.N)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With11 » N
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With11.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With11.index.html
new file mode 100644
index 0000000000..15f898e759
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With11.index.html
@@ -0,0 +1,43 @@
+
+
+ With11 (test.Ocamlary.With11)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With11
+
+
+ Module type Ocamlary.With11
+
+
+
+
+
+
module M
+ = With9
+
+
+
+
+
+
+
module
+ N
+ : M.S
+ with
+ type
+ t = int
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.N.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.N.index.html
new file mode 100644
index 0000000000..89fd4f5f32
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.N.index.html
@@ -0,0 +1,31 @@
+
+
+ N (test.Ocamlary.With8.M.N)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With8 »
+ M » N
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.index.html
new file mode 100644
index 0000000000..7735cf906e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.index.html
@@ -0,0 +1,55 @@
+
+
+ M (test.Ocamlary.With8.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With8 » M
+
+
+
+
+
+
+
+ module
+ type
+ S
+ = sig ...
+ end
+
+
+
+
+
+
+
+
module
+ N
+ : module
+ type of
+ struct
+ include
+ With5.N
+ end with
+
+ type
+ t =
+ With5.N.t
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.module-type-S.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.module-type-S.index.html
new file mode 100644
index 0000000000..86bcc2b771
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.M.module-type-S.index.html
@@ -0,0 +1,29 @@
+
+
+ S (test.Ocamlary.With8.M.S)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary »
+ With8 »
+ M » S
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Ocamlary.module-type-With8.index.html b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.index.html
new file mode 100644
index 0000000000..0668a281ec
--- /dev/null
+++ b/test/generators/cases_pre408/html/Ocamlary.module-type-With8.index.html
@@ -0,0 +1,41 @@
+
+
+ With8 (test.Ocamlary.With8)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Ocamlary » With8
+
+
+ Module type Ocamlary.With8
+
+
+
+
+
+
module
+ M
+ : module
+ type of
+ struct
+ include
+ With5
+ end with
+
+ type
+ N.t =
+ With5.N.t
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Section.index.html b/test/generators/cases_pre408/html/Section.index.html
new file mode 100644
index 0000000000..595f56fb59
--- /dev/null
+++ b/test/generators/cases_pre408/html/Section.index.html
@@ -0,0 +1,77 @@
+
+
+ Section (test.Section)
+
+
+
+
+
+
+
+ Up –
+ test » Section
+
+
+
+
+
+
+
+ Empty section
+
+
Text only
+
Foo bar.
+
Aside only
+ Foo bar.
+
Value only
+
+
+
+ Empty section
+
+
+
+ and one
+ with a nested section
+
+
+ This
+ section
title has markup
+
+
But links are impossible thanks to the parser, so we never have
+ trouble rendering a section title in a table of contents – no
+ link will be nested inside another link.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Stop.N.index.html b/test/generators/cases_pre408/html/Stop.N.index.html
new file mode 100644
index 0000000000..7b47fa687c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Stop.N.index.html
@@ -0,0 +1,27 @@
+
+
+ N (test.Stop.N)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Stop » N
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Stop.index.html b/test/generators/cases_pre408/html/Stop.index.html
new file mode 100644
index 0000000000..e6d9cfcd18
--- /dev/null
+++ b/test/generators/cases_pre408/html/Stop.index.html
@@ -0,0 +1,55 @@
+
+
+ Stop (test.Stop)
+
+
+
+
+
+
+
+ Up –
+ test » Stop
+
+
+
+
+
This is normal commented text.
+
+
The next value is bar
, and it should be missing from
+ the documentation. There is also an entire module, M
+ , which should also be hidden. It contains a nested stop comment,
+ but that stop comment should not turn documentation back on in this
+ outer module, because stop comments respect scope.
+
Documentation is on again.
+
Now, we have a nested module, and it has a stop comment between
+ its two items. We want to see that the first item is displayed,
+ but the second is missing, and the stop comment disables documenation
+ only in that module, and not in this outer module.
+
+
+
+
+
module
+ N
+ : sig ...
+ end
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Stop_dead_link_doc.Foo.index.html b/test/generators/cases_pre408/html/Stop_dead_link_doc.Foo.index.html
new file mode 100644
index 0000000000..efe4277bea
--- /dev/null
+++ b/test/generators/cases_pre408/html/Stop_dead_link_doc.Foo.index.html
@@ -0,0 +1,27 @@
+
+
+ Foo (test.Stop_dead_link_doc.Foo)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Stop_dead_link_doc » Foo
+
+
+ Module Stop_dead_link_doc.Foo
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Stop_dead_link_doc.index.html b/test/generators/cases_pre408/html/Stop_dead_link_doc.index.html
new file mode 100644
index 0000000000..bf85543eeb
--- /dev/null
+++ b/test/generators/cases_pre408/html/Stop_dead_link_doc.index.html
@@ -0,0 +1,146 @@
+
+
+ Stop_dead_link_doc (test.Stop_dead_link_doc)
+
+
+
+
+
+
+
+ Up –
+ test » Stop_dead_link_doc
+
+
+ Module Stop_dead_link_doc
+
+
+
+
+
+
module
+ Foo
+ : sig ...
+ end
+
+
+
+
+
+
+
+
type foo =
+
+
+
+
+
+ |
+ Bar
+ of
+ Foo.t
+
+
+
+
+
+
+
+
+
+
+
type bar =
+
+
+
+
+
+ |
+ Bar
+ of
+ {
+
+
+
+
+
+
+ field : Foo.t ;
+
+
+
+
}
+
+
+
+
+
+
+
+
+
type foo_
+ =
+
+
+
+
+
+ |
+ Bar_
+ of int *
+ Foo.t * int
+
+
+
+
+
+
+
+
+
+
+
type bar_
+ =
+
+
+
+
+
+ |
+ Bar__
+ of
+ Foo.t option
+
+
+
+
+
+
+
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.Alias.index.html b/test/generators/cases_pre408/html/Toplevel_comments.Alias.index.html
new file mode 100644
index 0000000000..149b7e5ecf
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.Alias.index.html
@@ -0,0 +1,28 @@
+
+
+ Alias (test.Toplevel_comments.Alias)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » Alias
+
+
+ Module Toplevel_comments.Alias
+ Doc of Alias
.
Doc of T
, part 2.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.Include_inline'.index.html b/test/generators/cases_pre408/html/Toplevel_comments.Include_inline'.index.html
new file mode 100644
index 0000000000..0da198a020
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.Include_inline'.index.html
@@ -0,0 +1,32 @@
+
+
+
+ Include_inline' (test.Toplevel_comments.Include_inline')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » Include_inline'
+
+
+ Module Toplevel_comments.Include_inline'
+ Doc of Include_inline
, part 1.
+ Doc of Include_inline
, part 2.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.Include_inline.index.html b/test/generators/cases_pre408/html/Toplevel_comments.Include_inline.index.html
new file mode 100644
index 0000000000..dca65ecfd9
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.Include_inline.index.html
@@ -0,0 +1,30 @@
+
+
+ Include_inline (test.Toplevel_comments.Include_inline)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » Include_inline
+
+
+ Module Toplevel_comments.Include_inline
+ Doc of T
, part 2.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.M''.index.html b/test/generators/cases_pre408/html/Toplevel_comments.M''.index.html
new file mode 100644
index 0000000000..6216e87184
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.M''.index.html
@@ -0,0 +1,21 @@
+
+
+ M'' (test.Toplevel_comments.M'')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » M''
+
+
+ Module Toplevel_comments.M''
+ Doc of M''
, part 1.
+ Doc of M''
, part 2.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.M'.index.html b/test/generators/cases_pre408/html/Toplevel_comments.M'.index.html
new file mode 100644
index 0000000000..26cc2e3d73
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.M'.index.html
@@ -0,0 +1,20 @@
+
+
+ M' (test.Toplevel_comments.M')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » M'
+
+
+ Module Toplevel_comments.M'
+ Doc of M'
from outside
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.M.index.html b/test/generators/cases_pre408/html/Toplevel_comments.M.index.html
new file mode 100644
index 0000000000..1d15ee8fb7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.M.index.html
@@ -0,0 +1,20 @@
+
+
+ M (test.Toplevel_comments.M)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » M
+
+
+ Module Toplevel_comments.M
+ Doc of M
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.class-c1.index.html b/test/generators/cases_pre408/html/Toplevel_comments.class-c1.index.html
new file mode 100644
index 0000000000..9e6dd9ae68
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.class-c1.index.html
@@ -0,0 +1,21 @@
+
+
+ c1 (test.Toplevel_comments.c1)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » c1
+
+
+ Class Toplevel_comments.c1
+ Doc of c1
, part 1.
+ Doc of c1
, part 2.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.class-c2.index.html b/test/generators/cases_pre408/html/Toplevel_comments.class-c2.index.html
new file mode 100644
index 0000000000..4b6a48e42e
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.class-c2.index.html
@@ -0,0 +1,20 @@
+
+
+ c2 (test.Toplevel_comments.c2)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » c2
+
+
+ Class Toplevel_comments.c2
+ Doc of c2
.
Doc of ct
, part 2.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.class-type-ct.index.html b/test/generators/cases_pre408/html/Toplevel_comments.class-type-ct.index.html
new file mode 100644
index 0000000000..0c52b3183c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.class-type-ct.index.html
@@ -0,0 +1,21 @@
+
+
+ ct (test.Toplevel_comments.ct)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » ct
+
+
+ Class type Toplevel_comments.ct
+ Doc of ct
, part 1.
+ Doc of ct
, part 2.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.index.html b/test/generators/cases_pre408/html/Toplevel_comments.index.html
new file mode 100644
index 0000000000..0937eb216c
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.index.html
@@ -0,0 +1,175 @@
+
+
+ Toplevel_comments (test.Toplevel_comments)
+
+
+
+
+
+
+
+ Up –
+ test » Toplevel_comments
+
+
+
+
+
+
+
+ module
+ type
+ T
+ = sig ...
+ end
+
+
+
+
+
+
+
+
Doc of Include_inline
, part 1.
+
+
+
+
+
+
+
Doc of Include_inline_T'
, part 1.
+
+
+
+
+
+
module
+ M
+ : sig ...
+ end
+
+
+
+
+
+
+
+
module
+ M'
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
module
+ M''
+ : sig ...
+ end
+
+
+
+
+
+
+
+
+
class
+ c1
+ : int ->
+ object ...
+ end
+
+
+
+
+
+
+
+
+ class
+ type
+ ct
+ = object ...
+ end
+
+
+
+
+
+
+
+
class
+ c2
+ : ct
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.module-type-Include_inline_T'.index.html b/test/generators/cases_pre408/html/Toplevel_comments.module-type-Include_inline_T'.index.html
new file mode 100644
index 0000000000..037a4f71ae
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.module-type-Include_inline_T'.index.html
@@ -0,0 +1,33 @@
+
+
+
+ Include_inline_T' (test.Toplevel_comments.Include_inline_T')
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » Include_inline_T'
+
+
+ Module type
+ Toplevel_comments.Include_inline_T'
+ Doc of Include_inline_T'
, part 1.
+ Doc of Include_inline_T'
, part 2.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.module-type-Include_inline_T.index.html b/test/generators/cases_pre408/html/Toplevel_comments.module-type-Include_inline_T.index.html
new file mode 100644
index 0000000000..4c84316f69
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.module-type-Include_inline_T.index.html
@@ -0,0 +1,32 @@
+
+
+
+ Include_inline_T (test.Toplevel_comments.Include_inline_T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » Include_inline_T
+
+
+ Module type
+ Toplevel_comments.Include_inline_T
+ Doc of T
, part 2.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Toplevel_comments.module-type-T.index.html b/test/generators/cases_pre408/html/Toplevel_comments.module-type-T.index.html
new file mode 100644
index 0000000000..2926e15b16
--- /dev/null
+++ b/test/generators/cases_pre408/html/Toplevel_comments.module-type-T.index.html
@@ -0,0 +1,28 @@
+
+
+ T (test.Toplevel_comments.T)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Toplevel_comments » T
+
+
+ Module type Toplevel_comments.T
+ Doc of T
, part 1.
Doc of T
, part 2.
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Type.index.html b/test/generators/cases_pre408/html/Type.index.html
new file mode 100644
index 0000000000..a522966af7
--- /dev/null
+++ b/test/generators/cases_pre408/html/Type.index.html
@@ -0,0 +1,879 @@
+
+
+ Type (test.Type)
+
+
+
+
+
+
+
+ Up –
+ test » Type
+
+
+
+
+
+
+
+
type alias
+ = int
+
+
+
+
+
+
+
type private_
+ = private int
+
+
+
+
+
+
+
+ type 'a constructor
+ = 'a
+
+
+
+
+
+
+
type arrow
+ = int -> int
+
+
+
+
+
+
+
+
type higher_order
+ =
+
+ (int -> int)
+ ->
+ int
+
+
+
+
+
+
+
+
type labeled
+ = l:int -> int
+
+
+
+
+
+
+
+
type optional
+ = ?l:int -> int
+
+
+
+
+
+
+
+
+ type labeled_higher_order
+ =
+
+ (l:int -> int)
+ ->
+
+
+ (?l:int -> int)
+ ->
+ int
+
+
+
+
+
+
+
+
type pair
+ = int * int
+
+
+
+
+
+
+
type parens_dropped
+ = int * int
+
+
+
+
+
+
+
type triple
+ = int * int * int
+
+
+
+
+
+
+
type nested_pair
+ = (int * int) * int
+
+
+
+
+
+
+
+
+
type variant_e
+ = {
+
+
}
+
+
+
+
+
+
type variant
+ =
+
+
+
+
+
+ | A
+
+
+
+
+
+
+ |
+ B
+ of int
+
+
+
+
+
+
+
+ | C
+
+
+ foo
+
+
+
+
+
+
+ | D
+
+
+
+ bar
+
+
+
+
+
+ |
+ E
+ of
+ variant_e
+
+
+
+
+
+
+
+
+
+
+
type variant_c
+ = {
+
+
}
+
+
+
+
+
+
type _ gadt
+ =
+
+
+
+
+
+ |
+ A :
+ int gadt
+
+
+
+
+
+
+
+ |
+ B : int
+ ->
+ string gadt
+
+
+
+
+
+
+
+ |
+ C :
+ variant_c
+ ->
+ unit gadt
+
+
+
+
+
+
+
+
+
+
+
type degenerate_gadt
+ =
+
+
+
+
+
+
+
+
type private_variant
+ = private
+
+
+
+
+
+
+
+
type record
+ = {
+
+
+
+
+
+ a : int;
+
+
+
+
+
+ mutable b : int;
+
+
+
+
+
+
+ c : int;
+
+ foo
+
+
+
+
+
+
+ d : int;
+
+
+ bar
+
+
+
+
+
+ e : a. 'a ;
+
+
+
}
+
+
+
+
+
+
type polymorphic_variant
+ = [
+
+
+
+
+
+ |
`A
+
+
+
+
+
+ |
+ `B of int
+
+
+
+
+
+ |
+ `C of int * unit
+
+
+
+
+
+
+ |
`D
+
+
+
]
+
+
+
+
+
+
+ type polymorphic_variant_extension
+ = [
+
+
]
+
+
+
+
+
+
+ type nested_polymorphic_variant
+ = [
+
+
+
+
+
+ |
+
+ `A of
+ [ `B | `C ]
+
+
+
+
+
]
+
+
+
+
+
+
+ type private_extenion#row
+
+
+
+
+
+
+
and private_extenion
+ = private
+ [>
+
+
]
+
+
+
+
+
+
type object_
+ = < a : int; b : int; c : int; >
+
+
+
+
+
+
+
+ module
+ type
+ X
+ = sig ...
+ end
+
+
+
+
+
+
+
+
type module_
+ =
+ (module
+ X )
+
+
+
+
+
+
+
+
+
type module_substitution
+ =
+ (module
+ X
+ with type
+ t = int
+ and type
+ u = unit)
+
+
+
+
+
+
+
+
+
+ type +'a covariant
+
+
+
+
+
+
+
+
+ type -'a contravariant
+
+
+
+
+
+
+
+
+ type _ bivariant
+ = int
+
+
+
+
+
+
+
+ type ('a, 'b) binary
+
+
+
+
+
+
+
+
type using_binary
+ =
+ (int, int) binary
+
+
+
+
+
+
+
+
+
+ type 'custom name
+
+
+
+
+
+
+
+
+ type 'a constrained
+ = 'a
+ constraint
+ 'a = int
+
+
+
+
+
+
+
+
+ type 'a exact_variant
+ = 'a
+ constraint
+ 'a =
+ [ `A | `B of int ]
+
+
+
+
+
+
+
+
+ type 'a lower_variant
+ = 'a
+ constraint
+ 'a =
+ [> `A | `B of int ]
+
+
+
+
+
+
+
+
+ type 'a any_variant
+ = 'a
+ constraint
+ 'a = [> ]
+
+
+
+
+
+
+
+
+ type 'a upper_variant
+ = 'a
+ constraint
+ 'a =
+ [< `A | `B of int ]
+
+
+
+
+
+
+
+
+
+ type 'a exact_object
+ = 'a
+ constraint
+ 'a =
+ < a : int; b : int; >
+
+
+
+
+
+
+
+
+ type 'a lower_object
+ = 'a
+ constraint
+ 'a =
+ < a : int; b : int; .. >
+
+
+
+
+
+
+
+
+ type 'a poly_object
+ = 'a
+ constraint
+ 'a =
+ < a : a. 'a ; >
+
+
+
+
+
+
+
+
+ type
+ ('a, 'b) double_constrained
+
+ = 'a *
+ 'b
+
+ constraint
+ 'a = int
+ constraint
+ 'b = unit
+
+
+
+
+
+
+
+
type as_
+ = int as 'a *
+ 'a
+
+
+
+
+
+
+
+
type extensible
+ = ..
+
+
+
+
+
+
+
+
type mutually
+ =
+
+
+
+
+
+
+
+
and recursive
+ =
+
+
+
+
+
+
+
+
exception
+ Foo
+ of int * int
+
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Type.module-type-X.index.html b/test/generators/cases_pre408/html/Type.module-type-X.index.html
new file mode 100644
index 0000000000..4e3dea7fbe
--- /dev/null
+++ b/test/generators/cases_pre408/html/Type.module-type-X.index.html
@@ -0,0 +1,33 @@
+
+
+ X (test.Type.X)
+
+
+
+
+
+
+
+ Up –
+ test »
+ Type » X
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/Val.index.html b/test/generators/cases_pre408/html/Val.index.html
new file mode 100644
index 0000000000..96cd937c7b
--- /dev/null
+++ b/test/generators/cases_pre408/html/Val.index.html
@@ -0,0 +1,41 @@
+
+
+ Val (test.Val)
+
+
+
+
+
+
+
+ Up –
+ test » Val
+
+
+
+
+
+
+
val documented : unit
+
+
+
+
+
+
+
val undocumented : unit
+
+
+
+
+
+
+
+ val documented_above : unit
+
+
+
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/html/dune b/test/generators/cases_pre408/html/dune
new file mode 100644
index 0000000000..1900258c3c
--- /dev/null
+++ b/test/generators/cases_pre408/html/dune
@@ -0,0 +1 @@
+(include html.dune.inc)
diff --git a/test/generators/cases_pre408/html/gen_html/dune b/test/generators/cases_pre408/html/gen_html/dune
new file mode 100644
index 0000000000..7bf6d5d0a0
--- /dev/null
+++ b/test/generators/cases_pre408/html/gen_html/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_html)
+ (libraries html_t_rule)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_pre408/html/gen_html/gen_html.ml b/test/generators/cases_pre408/html/gen_html/gen_html.ml
new file mode 100644
index 0000000000..9976d0a936
--- /dev/null
+++ b/test/generators/cases_pre408/html/gen_html/gen_html.ml
@@ -0,0 +1,6 @@
+let () =
+ let stanzas =
+ Gen_backend.gen_backend_rules "html" Html_t_rule.html_target_rule
+ Gen_backend.files "4.10"
+ in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_pre408/html/html.dune.inc b/test/generators/cases_pre408/html/html.dune.inc
new file mode 100644
index 0000000000..64fde50c6e
--- /dev/null
+++ b/test/generators/cases_pre408/html/html.dune.inc
@@ -0,0 +1,4002 @@
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../alias.odocl})
+ (with-stdout-to
+ Alias.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Alias/index.html'")))
+ (with-stdout-to
+ Alias.Foo__X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Alias/Foo__X/index.html'")))
+ (with-stdout-to
+ Alias.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Alias/X/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.index.html Alias.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.Foo__X.index.html Alias.Foo__X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.X.index.html Alias.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../bugs.odocl})
+ (with-stdout-to
+ Bugs.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Bugs/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs.index.html Bugs.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../bugs_pre_410.odocl})
+ (with-stdout-to
+ Bugs_pre_410.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Bugs_pre_410/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_pre_410.index.html Bugs_pre_410.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../class.odocl})
+ (with-stdout-to
+ Class.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/index.html'")))
+ (with-stdout-to
+ Class.class-type-empty.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-type-empty/index.html'")))
+ (with-stdout-to
+ Class.class-type-mutually.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-type-mutually/index.html'")))
+ (with-stdout-to
+ Class.class-type-recursive.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-type-recursive/index.html'")))
+ (with-stdout-to
+ Class.class-mutually'.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-mutually'\\''/index.html'")))
+ (with-stdout-to
+ Class.class-recursive'.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-recursive'\\''/index.html'")))
+ (with-stdout-to
+ Class.class-type-empty_virtual.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-type-empty_virtual/index.html'")))
+ (with-stdout-to
+ Class.class-empty_virtual'.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-empty_virtual'\\''/index.html'")))
+ (with-stdout-to
+ Class.class-type-polymorphic.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-type-polymorphic/index.html'")))
+ (with-stdout-to
+ Class.class-polymorphic'.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Class/class-polymorphic'\\''/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.index.html Class.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-type-empty.index.html
+ Class.class-type-empty.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-type-mutually.index.html
+ Class.class-type-mutually.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-type-recursive.index.html
+ Class.class-type-recursive.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-mutually'.index.html
+ Class.class-mutually'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-recursive'.index.html
+ Class.class-recursive'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-type-empty_virtual.index.html
+ Class.class-type-empty_virtual.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-empty_virtual'.index.html
+ Class.class-empty_virtual'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-type-polymorphic.index.html
+ Class.class-type-polymorphic.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Class.class-polymorphic'.index.html
+ Class.class-polymorphic'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../external.odocl})
+ (with-stdout-to
+ External.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/External/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff External.index.html External.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../functor.odocl})
+ (with-stdout-to
+ Functor.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/index.html'")))
+ (with-stdout-to
+ Functor.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/module-type-S/index.html'")))
+ (with-stdout-to
+ Functor.module-type-S1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/module-type-S1/index.html'")))
+ (with-stdout-to
+ Functor.module-type-S1.argument-1-_.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Functor/module-type-S1/argument-1-_/index.html'")))
+ (with-stdout-to
+ Functor.F1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F1/index.html'")))
+ (with-stdout-to
+ Functor.F1.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F1/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Functor.F2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F2/index.html'")))
+ (with-stdout-to
+ Functor.F2.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F2/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Functor.F3.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F3/index.html'")))
+ (with-stdout-to
+ Functor.F3.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F3/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Functor.F4.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F4/index.html'")))
+ (with-stdout-to
+ Functor.F4.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F4/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Functor.F5.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor/F5/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.index.html Functor.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.module-type-S.index.html
+ Functor.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.module-type-S1.index.html
+ Functor.module-type-S1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.module-type-S1.argument-1-_.index.html
+ Functor.module-type-S1.argument-1-_.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F1.index.html Functor.F1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.F1.argument-1-Arg.index.html
+ Functor.F1.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F2.index.html Functor.F2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.F2.argument-1-Arg.index.html
+ Functor.F2.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F3.index.html Functor.F3.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.F3.argument-1-Arg.index.html
+ Functor.F3.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F4.index.html Functor.F4.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor.F4.argument-1-Arg.index.html
+ Functor.F4.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F5.index.html Functor.F5.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../functor2.odocl})
+ (with-stdout-to
+ Functor2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor2/index.html'")))
+ (with-stdout-to
+ Functor2.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor2/module-type-S/index.html'")))
+ (with-stdout-to
+ Functor2.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor2/X/index.html'")))
+ (with-stdout-to
+ Functor2.X.argument-1-Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor2/X/argument-1-Y/index.html'")))
+ (with-stdout-to
+ Functor2.X.argument-2-Z.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor2/X/argument-2-Z/index.html'")))
+ (with-stdout-to
+ Functor2.module-type-XF.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Functor2/module-type-XF/index.html'")))
+ (with-stdout-to
+ Functor2.module-type-XF.argument-1-Y.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Functor2/module-type-XF/argument-1-Y/index.html'")))
+ (with-stdout-to
+ Functor2.module-type-XF.argument-2-Z.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Functor2/module-type-XF/argument-2-Z/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor2.index.html Functor2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor2.module-type-S.index.html
+ Functor2.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor2.X.index.html Functor2.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor2.X.argument-1-Y.index.html
+ Functor2.X.argument-1-Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor2.X.argument-2-Z.index.html
+ Functor2.X.argument-2-Z.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor2.module-type-XF.index.html
+ Functor2.module-type-XF.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor2.module-type-XF.argument-1-Y.index.html
+ Functor2.module-type-XF.argument-1-Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Functor2.module-type-XF.argument-2-Z.index.html
+ Functor2.module-type-XF.argument-2-Z.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../include.odocl})
+ (with-stdout-to
+ Include.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include/index.html'")))
+ (with-stdout-to
+ Include.module-type-Not_inlined.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Include/module-type-Not_inlined/index.html'")))
+ (with-stdout-to
+ Include.module-type-Inlined.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include/module-type-Inlined/index.html'")))
+ (with-stdout-to
+ Include.module-type-Not_inlined_and_closed.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Include/module-type-Not_inlined_and_closed/index.html'")))
+ (with-stdout-to
+ Include.module-type-Not_inlined_and_opened.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Include/module-type-Not_inlined_and_opened/index.html'")))
+ (with-stdout-to
+ Include.module-type-Inherent_Module.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Include/module-type-Inherent_Module/index.html'")))
+ (with-stdout-to
+ Include.module-type-Dorminant_Module.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Include/module-type-Dorminant_Module/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include.index.html Include.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include.module-type-Not_inlined.index.html
+ Include.module-type-Not_inlined.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include.module-type-Inlined.index.html
+ Include.module-type-Inlined.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include.module-type-Not_inlined_and_closed.index.html
+ Include.module-type-Not_inlined_and_closed.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include.module-type-Not_inlined_and_opened.index.html
+ Include.module-type-Not_inlined_and_opened.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include.module-type-Inherent_Module.index.html
+ Include.module-type-Inherent_Module.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include.module-type-Dorminant_Module.index.html
+ Include.module-type-Dorminant_Module.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../include2.odocl})
+ (with-stdout-to
+ Include2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include2/index.html'")))
+ (with-stdout-to
+ Include2.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include2/X/index.html'")))
+ (with-stdout-to
+ Include2.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include2/Y/index.html'")))
+ (with-stdout-to
+ Include2.Y_include_synopsis.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include2/Y_include_synopsis/index.html'")))
+ (with-stdout-to
+ Include2.Y_include_doc.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include2/Y_include_doc/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.index.html Include2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.X.index.html Include2.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.Y.index.html Include2.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include2.Y_include_synopsis.index.html
+ Include2.Y_include_synopsis.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include2.Y_include_doc.index.html
+ Include2.Y_include_doc.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run
+ odoc
+ html-generate
+ --indent
+ -o
+ html.gen
+ %{dep:../include_sections.odocl})
+ (with-stdout-to
+ Include_sections.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Include_sections/index.html'")))
+ (with-stdout-to
+ Include_sections.module-type-Something.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Include_sections/module-type-Something/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include_sections.index.html Include_sections.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Include_sections.module-type-Something.index.html
+ Include_sections.module-type-Something.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../interlude.odocl})
+ (with-stdout-to
+ Interlude.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Interlude/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Interlude.index.html Interlude.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../markup.odocl})
+ (with-stdout-to
+ Markup.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Markup/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Markup.index.html Markup.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../page-mld.odocl})
+ (with-stdout-to
+ mld.html.gen
+ (progn
+ (system "cat 'html.gen/test/mld.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff mld.html mld.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../module.odocl})
+ (with-stdout-to
+ Module.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/index.html'")))
+ (with-stdout-to
+ Module.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S/index.html'")))
+ (with-stdout-to
+ Module.module-type-S.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S/M/index.html'")))
+ (with-stdout-to
+ Module.module-type-S2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S2/index.html'")))
+ (with-stdout-to
+ Module.module-type-S2.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S2/M/index.html'")))
+ (with-stdout-to
+ Module.module-type-S3.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S3/index.html'")))
+ (with-stdout-to
+ Module.module-type-S3.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S3/M/index.html'")))
+ (with-stdout-to
+ Module.module-type-S4.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S4/index.html'")))
+ (with-stdout-to
+ Module.module-type-S4.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S4/M/index.html'")))
+ (with-stdout-to
+ Module.module-type-S5.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S5/index.html'")))
+ (with-stdout-to
+ Module.module-type-S5.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S5/M/index.html'")))
+ (with-stdout-to
+ Module.module-type-S6.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S6/index.html'")))
+ (with-stdout-to
+ Module.module-type-S6.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S6/M/index.html'")))
+ (with-stdout-to
+ Module.M'.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/M'\\''/index.html'")))
+ (with-stdout-to
+ Module.module-type-S7.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S7/index.html'")))
+ (with-stdout-to
+ Module.module-type-S8.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S8/index.html'")))
+ (with-stdout-to
+ Module.module-type-S9.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/module-type-S9/index.html'")))
+ (with-stdout-to
+ Module.Mutually.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/Mutually/index.html'")))
+ (with-stdout-to
+ Module.Recursive.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Module/Recursive/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.index.html Module.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.module-type-S.index.html Module.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S.M.index.html
+ Module.module-type-S.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S2.index.html
+ Module.module-type-S2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S2.M.index.html
+ Module.module-type-S2.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S3.index.html
+ Module.module-type-S3.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S3.M.index.html
+ Module.module-type-S3.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S4.index.html
+ Module.module-type-S4.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S4.M.index.html
+ Module.module-type-S4.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S5.index.html
+ Module.module-type-S5.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S5.M.index.html
+ Module.module-type-S5.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S6.index.html
+ Module.module-type-S6.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S6.M.index.html
+ Module.module-type-S6.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.M'.index.html Module.M'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S7.index.html
+ Module.module-type-S7.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S8.index.html
+ Module.module-type-S8.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Module.module-type-S9.index.html
+ Module.module-type-S9.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.Mutually.index.html Module.Mutually.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.Recursive.index.html Module.Recursive.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../nested.odocl})
+ (with-stdout-to
+ Nested.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/index.html'")))
+ (with-stdout-to
+ Nested.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/X/index.html'")))
+ (with-stdout-to
+ Nested.module-type-Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/module-type-Y/index.html'")))
+ (with-stdout-to
+ Nested.F.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/F/index.html'")))
+ (with-stdout-to
+ Nested.F.argument-1-Arg1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/F/argument-1-Arg1/index.html'")))
+ (with-stdout-to
+ Nested.F.argument-2-Arg2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/F/argument-2-Arg2/index.html'")))
+ (with-stdout-to
+ Nested.class-z.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/class-z/index.html'")))
+ (with-stdout-to
+ Nested.class-inherits.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Nested/class-inherits/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.index.html Nested.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.X.index.html Nested.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.module-type-Y.index.html Nested.module-type-Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.F.index.html Nested.F.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Nested.F.argument-1-Arg1.index.html
+ Nested.F.argument-1-Arg1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Nested.F.argument-2-Arg2.index.html
+ Nested.F.argument-2-Arg2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.class-z.index.html Nested.class-z.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Nested.class-inherits.index.html
+ Nested.class-inherits.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../ocamlary.odocl})
+ (with-stdout-to
+ Ocamlary.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/index.html'")))
+ (with-stdout-to
+ Ocamlary.Empty.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Empty/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-Empty.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-Empty/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MissingComment.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-MissingComment/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-EmptySig.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-EmptySig/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-EmptySigAlias.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-EmptySigAlias/index.html'")))
+ (with-stdout-to
+ Ocamlary.ModuleWithSignature.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/ModuleWithSignature/index.html'")))
+ (with-stdout-to
+ Ocamlary.ModuleWithSignatureAlias.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/ModuleWithSignatureAlias/index.html'")))
+ (with-stdout-to
+ Ocamlary.One.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/One/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SigForMod.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-SigForMod/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SigForMod.Inner.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SigForMod/Inner/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SigForMod.Inner.module-type-Empty.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SigForMod/Inner/module-type-Empty/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-SuperSig/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.module-type-SubSigA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SuperSig/module-type-SubSigA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SuperSig/module-type-SubSigA/SubSigAMod/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.module-type-SubSigB.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SuperSig/module-type-SubSigB/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.module-type-EmptySig.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SuperSig/module-type-EmptySig/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.module-type-One.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SuperSig/module-type-One/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-SuperSig.module-type-SuperSig.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-SuperSig/module-type-SuperSig/index.html'")))
+ (with-stdout-to
+ Ocamlary.Buffer.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Buffer/index.html'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/CollectionModule/index.html'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CollectionModule/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CollectionModule/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CollectionModule/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CollectionModule/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-COLLECTION.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-COLLECTION/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-COLLECTION.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-COLLECTION/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-COLLECTION/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-COLLECTION/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-COLLECTION.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-COLLECTION/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Recollection/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.argument-1-C.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/argument-1-C/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/argument-1-C/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/argument-1-C/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/argument-1-C/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.argument-1-C.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/argument-1-C/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.Recollection.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Recollection/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MMM.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-MMM/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MMM.C.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-MMM/C/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MMM.C.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-MMM/C/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-MMM/C/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-MMM/C/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-MMM.C.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-MMM/C/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-RECOLLECTION.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-RECOLLECTION/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-RecollectionModule.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-RecollectionModule/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-RecollectionModule/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-RecollectionModule/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-RecollectionModule/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-RecollectionModule.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-RecollectionModule/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-A.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-A/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-A.Q.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-A/Q/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-A.Q.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-A/Q/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-A/Q/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-A/Q/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-A.Q.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-A/Q/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-B.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-B/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-B.Q.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-B/Q/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-B.Q.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-B/Q/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-B/Q/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-B/Q/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-B.Q.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-B/Q/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-C.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-C/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-C.Q.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-C/Q/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-C.Q.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-C/Q/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-C/Q/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-C/Q/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-C.Q.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-C/Q/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/FunctorTypeOf/index.html'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.argument-1-Collection.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/FunctorTypeOf/argument-1-Collection/index.html'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/FunctorTypeOf/argument-1-Collection/InnerModuleA/index.html'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/FunctorTypeOf/argument-1-Collection/InnerModuleA/InnerModuleA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/FunctorTypeOf/argument-1-Collection/InnerModuleA/module-type-InnerModuleTypeA'\\''/index.html'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.argument-1-Collection.module-type-InnerModuleTypeA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/FunctorTypeOf/argument-1-Collection/module-type-InnerModuleTypeA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-IncludeModuleType.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-IncludeModuleType/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-ToInclude.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-ToInclude/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-ToInclude.IncludedA.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-ToInclude/IncludedA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-ToInclude.module-type-IncludedB.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-ToInclude/module-type-IncludedB/index.html'")))
+ (with-stdout-to
+ Ocamlary.IncludedA.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/IncludedA/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-IncludedB.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-IncludedB/index.html'")))
+ (with-stdout-to
+ Ocamlary.ExtMod.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/ExtMod/index.html'")))
+ (with-stdout-to
+ Ocamlary.class-empty_class.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/class-empty_class/index.html'")))
+ (with-stdout-to
+ Ocamlary.class-one_method_class.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/class-one_method_class/index.html'")))
+ (with-stdout-to
+ Ocamlary.class-two_method_class.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/class-two_method_class/index.html'")))
+ (with-stdout-to
+ Ocamlary.class-param_class.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/class-param_class/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep1/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep1.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep1/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep1.module-type-S.class-c.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Dep1/module-type-S/class-c/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep1.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep1/X/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep1.X.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep1/X/Y/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep1.X.Y.class-c.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep1/X/Y/class-c/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep2/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep2.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep2/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep2.argument-1-Arg.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep2/argument-1-Arg/X/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep2.A.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep2/A/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep3.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep3/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep4.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep4/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep4.module-type-T.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep4/module-type-T/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep4.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep4/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep4.module-type-S.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep4/module-type-S/X/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep4.module-type-S.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep4/module-type-S/Y/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep4.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep4/X/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep5.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep5/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep5.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep5/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep5.argument-1-Arg.module-type-S.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Dep5/argument-1-Arg/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Dep5/argument-1-Arg/module-type-S/Y/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep5.Z.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep5/Z/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.module-type-T.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/module-type-T/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.module-type-T.module-type-R.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Dep6/module-type-T/module-type-R/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.module-type-T.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/module-type-T/Y/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/X/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.X.module-type-R.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/X/module-type-R/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep6.X.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep6/X/Y/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep7.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep7/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep7.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep7/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep7.argument-1-Arg.module-type-T.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Dep7/argument-1-Arg/module-type-T/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep7.argument-1-Arg.X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep7/argument-1-Arg/X/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep7.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep7/M/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep8.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep8/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep8.module-type-T.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep8/module-type-T/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep9.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep9/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep9.argument-1-X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep9/argument-1-X/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-Dep10.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-Dep10/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep11.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep11/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep11.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep11/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep11.module-type-S.class-c.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/Dep11/module-type-S/class-c/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep12.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep12/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep12.argument-1-Arg.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep12/argument-1-Arg/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep13.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep13/index.html'")))
+ (with-stdout-to
+ Ocamlary.Dep13.class-c.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Dep13/class-c/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With1/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With1.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With1/M/index.html'")))
+ (with-stdout-to
+ Ocamlary.With2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With2/index.html'")))
+ (with-stdout-to
+ Ocamlary.With2.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With2/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.With3.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With3/index.html'")))
+ (with-stdout-to
+ Ocamlary.With3.N.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With3/N/index.html'")))
+ (with-stdout-to
+ Ocamlary.With4.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With4/index.html'")))
+ (with-stdout-to
+ Ocamlary.With4.N.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With4/N/index.html'")))
+ (with-stdout-to
+ Ocamlary.With5.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With5/index.html'")))
+ (with-stdout-to
+ Ocamlary.With5.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With5/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.With5.N.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With5/N/index.html'")))
+ (with-stdout-to
+ Ocamlary.With6.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With6/index.html'")))
+ (with-stdout-to
+ Ocamlary.With6.module-type-T.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With6/module-type-T/index.html'")))
+ (with-stdout-to
+ Ocamlary.With6.module-type-T.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With6/module-type-T/M/index.html'")))
+ (with-stdout-to
+ Ocamlary.With7.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With7/index.html'")))
+ (with-stdout-to
+ Ocamlary.With7.argument-1-X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With7/argument-1-X/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With8.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With8/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With8.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With8/M/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With8.M.module-type-S.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-With8/M/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With8.M.N.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With8/M/N/index.html'")))
+ (with-stdout-to
+ Ocamlary.With9.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With9/index.html'")))
+ (with-stdout-to
+ Ocamlary.With9.module-type-S.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With9/module-type-S/index.html'")))
+ (with-stdout-to
+ Ocamlary.With10.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With10/index.html'")))
+ (with-stdout-to
+ Ocamlary.With10.module-type-T.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/With10/module-type-T/index.html'")))
+ (with-stdout-to
+ Ocamlary.With10.module-type-T.M.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/With10/module-type-T/M/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With11.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With11/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-With11.N.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-With11/N/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-NestedInclude1.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-NestedInclude1/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-NestedInclude1/module-type-NestedInclude2/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-NestedInclude2.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-NestedInclude2/index.html'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/DoubleInclude1/index.html'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude1.DoubleInclude2.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/DoubleInclude1/DoubleInclude2/index.html'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude3.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/DoubleInclude3/index.html'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude3.DoubleInclude2.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/DoubleInclude3/DoubleInclude2/index.html'")))
+ (with-stdout-to
+ Ocamlary.IncludeInclude1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/IncludeInclude1/index.html'")))
+ (with-stdout-to
+ Ocamlary.IncludeInclude1.module-type-IncludeInclude2.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/IncludeInclude1/module-type-IncludeInclude2/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-IncludeInclude2.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-IncludeInclude2/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/CanonicalTest/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__List.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CanonicalTest/Base__List/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/CanonicalTest/Base__/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/CanonicalTest/Base/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base.List.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CanonicalTest/Base/List/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__Tests.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CanonicalTest/Base__Tests/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__Tests.C.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CanonicalTest/Base__Tests/C/index.html'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.List_modif.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/CanonicalTest/List_modif/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__A.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo__A/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__B.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo__B/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__C.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo__C/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__D.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo__D/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__E.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo__E/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo__/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.A.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo/A/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.B.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo/B/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.C.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo/C/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.D.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo/D/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.E.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Foo/E/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Std.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/Std/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.E.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/E/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.P1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/P1/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.P1.Y.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/P1/Y/index.html'")))
+ (with-stdout-to
+ Ocamlary.Aliases.P2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Aliases/P2/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-M/index.html'")))
+ (with-stdout-to
+ Ocamlary.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/M/index.html'")))
+ (with-stdout-to
+ Ocamlary.Only_a_module.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/Only_a_module/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-TypeExt.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Ocamlary/module-type-TypeExt/index.html'")))
+ (with-stdout-to
+ Ocamlary.module-type-TypeExtPruned.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Ocamlary/module-type-TypeExtPruned/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.index.html Ocamlary.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Empty.index.html Ocamlary.Empty.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-Empty.index.html
+ Ocamlary.module-type-Empty.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MissingComment.index.html
+ Ocamlary.module-type-MissingComment.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-EmptySig.index.html
+ Ocamlary.module-type-EmptySig.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-EmptySigAlias.index.html
+ Ocamlary.module-type-EmptySigAlias.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.ModuleWithSignature.index.html
+ Ocamlary.ModuleWithSignature.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.ModuleWithSignatureAlias.index.html
+ Ocamlary.ModuleWithSignatureAlias.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.One.index.html Ocamlary.One.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SigForMod.index.html
+ Ocamlary.module-type-SigForMod.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SigForMod.Inner.index.html
+ Ocamlary.module-type-SigForMod.Inner.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SigForMod.Inner.module-type-Empty.index.html
+ Ocamlary.module-type-SigForMod.Inner.module-type-Empty.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.index.html
+ Ocamlary.module-type-SuperSig.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.module-type-SubSigA.index.html
+ Ocamlary.module-type-SuperSig.module-type-SubSigA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.index.html
+ Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.module-type-SubSigB.index.html
+ Ocamlary.module-type-SuperSig.module-type-SubSigB.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.module-type-EmptySig.index.html
+ Ocamlary.module-type-SuperSig.module-type-EmptySig.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.module-type-One.index.html
+ Ocamlary.module-type-SuperSig.module-type-One.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-SuperSig.module-type-SuperSig.index.html
+ Ocamlary.module-type-SuperSig.module-type-SuperSig.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Buffer.index.html Ocamlary.Buffer.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.index.html
+ Ocamlary.CollectionModule.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.InnerModuleA.index.html
+ Ocamlary.CollectionModule.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.module-type-InnerModuleTypeA.index.html
+ Ocamlary.CollectionModule.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-COLLECTION.index.html
+ Ocamlary.module-type-COLLECTION.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-COLLECTION.InnerModuleA.index.html
+ Ocamlary.module-type-COLLECTION.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-COLLECTION.module-type-InnerModuleTypeA.index.html
+ Ocamlary.module-type-COLLECTION.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.index.html
+ Ocamlary.Recollection.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.argument-1-C.index.html
+ Ocamlary.Recollection.argument-1-C.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.index.html
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.argument-1-C.module-type-InnerModuleTypeA.index.html
+ Ocamlary.Recollection.argument-1-C.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.InnerModuleA.index.html
+ Ocamlary.Recollection.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.module-type-InnerModuleTypeA.index.html
+ Ocamlary.Recollection.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MMM.index.html
+ Ocamlary.module-type-MMM.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MMM.C.index.html
+ Ocamlary.module-type-MMM.C.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MMM.C.InnerModuleA.index.html
+ Ocamlary.module-type-MMM.C.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-MMM.C.module-type-InnerModuleTypeA.index.html
+ Ocamlary.module-type-MMM.C.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-RECOLLECTION.index.html
+ Ocamlary.module-type-RECOLLECTION.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-RecollectionModule.index.html
+ Ocamlary.module-type-RecollectionModule.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.index.html
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-RecollectionModule.module-type-InnerModuleTypeA.index.html
+ Ocamlary.module-type-RecollectionModule.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-A.index.html
+ Ocamlary.module-type-A.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-A.Q.index.html
+ Ocamlary.module-type-A.Q.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-A.Q.InnerModuleA.index.html
+ Ocamlary.module-type-A.Q.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-A.Q.module-type-InnerModuleTypeA.index.html
+ Ocamlary.module-type-A.Q.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-B.index.html
+ Ocamlary.module-type-B.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-B.Q.index.html
+ Ocamlary.module-type-B.Q.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-B.Q.InnerModuleA.index.html
+ Ocamlary.module-type-B.Q.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-B.Q.module-type-InnerModuleTypeA.index.html
+ Ocamlary.module-type-B.Q.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-C.index.html
+ Ocamlary.module-type-C.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-C.Q.index.html
+ Ocamlary.module-type-C.Q.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-C.Q.InnerModuleA.index.html
+ Ocamlary.module-type-C.Q.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-C.Q.module-type-InnerModuleTypeA.index.html
+ Ocamlary.module-type-C.Q.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.FunctorTypeOf.index.html
+ Ocamlary.FunctorTypeOf.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.FunctorTypeOf.argument-1-Collection.index.html
+ Ocamlary.FunctorTypeOf.argument-1-Collection.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.index.html
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.index.html
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.index.html
+ Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.FunctorTypeOf.argument-1-Collection.module-type-InnerModuleTypeA.index.html
+ Ocamlary.FunctorTypeOf.argument-1-Collection.module-type-InnerModuleTypeA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-IncludeModuleType.index.html
+ Ocamlary.module-type-IncludeModuleType.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-ToInclude.index.html
+ Ocamlary.module-type-ToInclude.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-ToInclude.IncludedA.index.html
+ Ocamlary.module-type-ToInclude.IncludedA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-ToInclude.module-type-IncludedB.index.html
+ Ocamlary.module-type-ToInclude.module-type-IncludedB.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.IncludedA.index.html Ocamlary.IncludedA.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-IncludedB.index.html
+ Ocamlary.module-type-IncludedB.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.ExtMod.index.html Ocamlary.ExtMod.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.class-empty_class.index.html
+ Ocamlary.class-empty_class.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.class-one_method_class.index.html
+ Ocamlary.class-one_method_class.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.class-two_method_class.index.html
+ Ocamlary.class-two_method_class.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.class-param_class.index.html
+ Ocamlary.class-param_class.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.index.html Ocamlary.Dep1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep1.module-type-S.index.html
+ Ocamlary.Dep1.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep1.module-type-S.class-c.index.html
+ Ocamlary.Dep1.module-type-S.class-c.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.X.index.html Ocamlary.Dep1.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.X.Y.index.html Ocamlary.Dep1.X.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep1.X.Y.class-c.index.html
+ Ocamlary.Dep1.X.Y.class-c.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep2.index.html Ocamlary.Dep2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep2.argument-1-Arg.index.html
+ Ocamlary.Dep2.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep2.argument-1-Arg.X.index.html
+ Ocamlary.Dep2.argument-1-Arg.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep2.A.index.html Ocamlary.Dep2.A.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep3.index.html Ocamlary.Dep3.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep4.index.html Ocamlary.Dep4.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep4.module-type-T.index.html
+ Ocamlary.Dep4.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep4.module-type-S.index.html
+ Ocamlary.Dep4.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep4.module-type-S.X.index.html
+ Ocamlary.Dep4.module-type-S.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep4.module-type-S.Y.index.html
+ Ocamlary.Dep4.module-type-S.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep4.X.index.html Ocamlary.Dep4.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep5.index.html Ocamlary.Dep5.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep5.argument-1-Arg.index.html
+ Ocamlary.Dep5.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep5.argument-1-Arg.module-type-S.index.html
+ Ocamlary.Dep5.argument-1-Arg.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.index.html
+ Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep5.Z.index.html Ocamlary.Dep5.Z.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep6.index.html Ocamlary.Dep6.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep6.module-type-S.index.html
+ Ocamlary.Dep6.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep6.module-type-T.index.html
+ Ocamlary.Dep6.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep6.module-type-T.module-type-R.index.html
+ Ocamlary.Dep6.module-type-T.module-type-R.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep6.module-type-T.Y.index.html
+ Ocamlary.Dep6.module-type-T.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep6.X.index.html Ocamlary.Dep6.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep6.X.module-type-R.index.html
+ Ocamlary.Dep6.X.module-type-R.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep6.X.Y.index.html Ocamlary.Dep6.X.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep7.index.html Ocamlary.Dep7.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep7.argument-1-Arg.index.html
+ Ocamlary.Dep7.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep7.argument-1-Arg.module-type-T.index.html
+ Ocamlary.Dep7.argument-1-Arg.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep7.argument-1-Arg.X.index.html
+ Ocamlary.Dep7.argument-1-Arg.X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep7.M.index.html Ocamlary.Dep7.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep8.index.html Ocamlary.Dep8.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep8.module-type-T.index.html
+ Ocamlary.Dep8.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep9.index.html Ocamlary.Dep9.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep9.argument-1-X.index.html
+ Ocamlary.Dep9.argument-1-X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-Dep10.index.html
+ Ocamlary.module-type-Dep10.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep11.index.html Ocamlary.Dep11.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep11.module-type-S.index.html
+ Ocamlary.Dep11.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep11.module-type-S.class-c.index.html
+ Ocamlary.Dep11.module-type-S.class-c.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep12.index.html Ocamlary.Dep12.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep12.argument-1-Arg.index.html
+ Ocamlary.Dep12.argument-1-Arg.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep13.index.html Ocamlary.Dep13.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Dep13.class-c.index.html
+ Ocamlary.Dep13.class-c.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With1.index.html
+ Ocamlary.module-type-With1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With1.M.index.html
+ Ocamlary.module-type-With1.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With2.index.html Ocamlary.With2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With2.module-type-S.index.html
+ Ocamlary.With2.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With3.index.html Ocamlary.With3.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With3.N.index.html Ocamlary.With3.N.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With4.index.html Ocamlary.With4.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With4.N.index.html Ocamlary.With4.N.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With5.index.html Ocamlary.With5.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With5.module-type-S.index.html
+ Ocamlary.With5.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With5.N.index.html Ocamlary.With5.N.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With6.index.html Ocamlary.With6.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With6.module-type-T.index.html
+ Ocamlary.With6.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With6.module-type-T.M.index.html
+ Ocamlary.With6.module-type-T.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With7.index.html Ocamlary.With7.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With7.argument-1-X.index.html
+ Ocamlary.With7.argument-1-X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With8.index.html
+ Ocamlary.module-type-With8.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With8.M.index.html
+ Ocamlary.module-type-With8.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With8.M.module-type-S.index.html
+ Ocamlary.module-type-With8.M.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With8.M.N.index.html
+ Ocamlary.module-type-With8.M.N.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With9.index.html Ocamlary.With9.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With9.module-type-S.index.html
+ Ocamlary.With9.module-type-S.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With10.index.html Ocamlary.With10.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With10.module-type-T.index.html
+ Ocamlary.With10.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.With10.module-type-T.M.index.html
+ Ocamlary.With10.module-type-T.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With11.index.html
+ Ocamlary.module-type-With11.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-With11.N.index.html
+ Ocamlary.module-type-With11.N.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-NestedInclude1.index.html
+ Ocamlary.module-type-NestedInclude1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.index.html
+ Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-NestedInclude2.index.html
+ Ocamlary.module-type-NestedInclude2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.DoubleInclude1.index.html
+ Ocamlary.DoubleInclude1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.DoubleInclude1.DoubleInclude2.index.html
+ Ocamlary.DoubleInclude1.DoubleInclude2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.DoubleInclude3.index.html
+ Ocamlary.DoubleInclude3.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.DoubleInclude3.DoubleInclude2.index.html
+ Ocamlary.DoubleInclude3.DoubleInclude2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.IncludeInclude1.index.html
+ Ocamlary.IncludeInclude1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.IncludeInclude1.module-type-IncludeInclude2.index.html
+ Ocamlary.IncludeInclude1.module-type-IncludeInclude2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-IncludeInclude2.index.html
+ Ocamlary.module-type-IncludeInclude2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.index.html
+ Ocamlary.CanonicalTest.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__List.index.html
+ Ocamlary.CanonicalTest.Base__List.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__.index.html
+ Ocamlary.CanonicalTest.Base__.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base.index.html
+ Ocamlary.CanonicalTest.Base.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base.List.index.html
+ Ocamlary.CanonicalTest.Base.List.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__Tests.index.html
+ Ocamlary.CanonicalTest.Base__Tests.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__Tests.C.index.html
+ Ocamlary.CanonicalTest.Base__Tests.C.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.List_modif.index.html
+ Ocamlary.CanonicalTest.List_modif.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.index.html Ocamlary.Aliases.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo__A.index.html
+ Ocamlary.Aliases.Foo__A.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo__B.index.html
+ Ocamlary.Aliases.Foo__B.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo__C.index.html
+ Ocamlary.Aliases.Foo__C.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo__D.index.html
+ Ocamlary.Aliases.Foo__D.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo__E.index.html
+ Ocamlary.Aliases.Foo__E.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo__.index.html
+ Ocamlary.Aliases.Foo__.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.index.html Ocamlary.Aliases.Foo.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo.A.index.html
+ Ocamlary.Aliases.Foo.A.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo.B.index.html
+ Ocamlary.Aliases.Foo.B.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo.C.index.html
+ Ocamlary.Aliases.Foo.C.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo.D.index.html
+ Ocamlary.Aliases.Foo.D.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.Foo.E.index.html
+ Ocamlary.Aliases.Foo.E.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Std.index.html Ocamlary.Aliases.Std.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.E.index.html Ocamlary.Aliases.E.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.P1.index.html Ocamlary.Aliases.P1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Aliases.P1.Y.index.html
+ Ocamlary.Aliases.P1.Y.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.P2.index.html Ocamlary.Aliases.P2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-M.index.html
+ Ocamlary.module-type-M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.M.index.html Ocamlary.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Only_a_module.index.html
+ Ocamlary.Only_a_module.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-TypeExt.index.html
+ Ocamlary.module-type-TypeExt.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.module-type-TypeExtPruned.index.html
+ Ocamlary.module-type-TypeExtPruned.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../section.odocl})
+ (with-stdout-to
+ Section.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Section/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Section.index.html Section.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../stop.odocl})
+ (with-stdout-to
+ Stop.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Stop/index.html'")))
+ (with-stdout-to
+ Stop.N.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Stop/N/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop.index.html Stop.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop.N.index.html Stop.N.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run
+ odoc
+ html-generate
+ --indent
+ -o
+ html.gen
+ %{dep:../stop_dead_link_doc.odocl})
+ (with-stdout-to
+ Stop_dead_link_doc.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Stop_dead_link_doc/index.html'")))
+ (with-stdout-to
+ Stop_dead_link_doc.Foo.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Stop_dead_link_doc/Foo/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop_dead_link_doc.index.html Stop_dead_link_doc.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Stop_dead_link_doc.Foo.index.html
+ Stop_dead_link_doc.Foo.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run
+ odoc
+ html-generate
+ --indent
+ -o
+ html.gen
+ %{dep:../toplevel_comments.odocl})
+ (with-stdout-to
+ Toplevel_comments.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.module-type-T.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Toplevel_comments/module-type-T/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.Include_inline.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Toplevel_comments/Include_inline/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.Include_inline'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Toplevel_comments/Include_inline'\\''/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.module-type-Include_inline_T.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Toplevel_comments/module-type-Include_inline_T/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.module-type-Include_inline_T'.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Toplevel_comments/module-type-Include_inline_T'\\''/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.M.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/M/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.M'.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/M'\\''/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.M''.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/M'\\'''\\''/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.Alias.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/Alias/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.class-c1.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/class-c1/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.class-type-ct.index.html.gen
+ (progn
+ (system
+ "cat 'html.gen/test/Toplevel_comments/class-type-ct/index.html'")))
+ (with-stdout-to
+ Toplevel_comments.class-c2.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Toplevel_comments/class-c2/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.index.html Toplevel_comments.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.module-type-T.index.html
+ Toplevel_comments.module-type-T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.Include_inline.index.html
+ Toplevel_comments.Include_inline.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.Include_inline'.index.html
+ Toplevel_comments.Include_inline'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.module-type-Include_inline_T.index.html
+ Toplevel_comments.module-type-Include_inline_T.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.module-type-Include_inline_T'.index.html
+ Toplevel_comments.module-type-Include_inline_T'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.M.index.html Toplevel_comments.M.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.M'.index.html Toplevel_comments.M'.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.M''.index.html
+ Toplevel_comments.M''.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.Alias.index.html
+ Toplevel_comments.Alias.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.class-c1.index.html
+ Toplevel_comments.class-c1.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.class-type-ct.index.html
+ Toplevel_comments.class-type-ct.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.class-c2.index.html
+ Toplevel_comments.class-c2.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../type.odocl})
+ (with-stdout-to
+ Type.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Type/index.html'")))
+ (with-stdout-to
+ Type.module-type-X.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Type/module-type-X/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Type.index.html Type.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Type.module-type-X.index.html Type.module-type-X.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc html-generate --indent -o html.gen %{dep:../val.odocl})
+ (with-stdout-to
+ Val.index.html.gen
+ (progn
+ (system "cat 'html.gen/test/Val/index.html'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Val.index.html Val.index.html.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
diff --git a/test/generators/cases_pre408/html/mld.html b/test/generators/cases_pre408/html/mld.html
new file mode 100644
index 0000000000..06e3fba16e
--- /dev/null
+++ b/test/generators/cases_pre408/html/mld.html
@@ -0,0 +1,45 @@
+
+
+ mld (test.mld)
+
+
+
+
+
+
+
+ Up –
+ test » mld
+
+
+ Mld Page
+ This is an .mld
file. It doesn't have an auto-generated
+ title, like modules and other pages generated fully by odoc do.
+
It will have a TOC generated from section headings.
+
+
+
+
+
+
Section
+
This is a section.
Another paragraph in section.
+
+ Another section
+ This is another section.
Another paragraph in section 2.
+
Subsection
+ This is a subsection.
Another paragraph in subsection.
+
Yet another paragraph in subsection.
+
+ Another Subsection
+ This is another subsection.
+
Another paragraph in subsection 2.
+
Yet another paragraph in subsection 2.
+
+
+
\ No newline at end of file
diff --git a/test/generators/cases_pre408/latex/Alias.X.tex b/test/generators/cases_pre408/latex/Alias.X.tex
new file mode 100644
index 0000000000..5d5900f8c5
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Alias.X.tex
@@ -0,0 +1,5 @@
+\section{Module \ocamlinlinecode{Alias.\allowbreak{}X}}\label{container-page-test-module-Alias-module-X}%
+\label{container-page-test-module-Alias-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Alias.tex b/test/generators/cases_pre408/latex/Alias.tex
new file mode 100644
index 0000000000..240cb64a62
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Alias.tex
@@ -0,0 +1,8 @@
+\section{Module \ocamlinlinecode{Alias}}\label{container-page-test-module-Alias}%
+\label{container-page-test-module-Alias-module-Foo+u++u+X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Alias-module-Foo+u++u+X]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Alias-module-Foo+u++u+X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[xref-unresolved]{\ocamlinlinecode{int}}}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Alias-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+
+\input{test/Alias.X.tex}
diff --git a/test/generators/cases_pre408/latex/Bugs.tex b/test/generators/cases_pre408/latex/Bugs.tex
new file mode 100644
index 0000000000..b32094ab37
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Bugs.tex
@@ -0,0 +1,6 @@
+\section{Module \ocamlinlinecode{Bugs}}\label{container-page-test-module-Bugs}%
+\label{container-page-test-module-Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\
+\label{container-page-test-module-Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : ?bar:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Bugs_pre_410.tex b/test/generators/cases_pre408/latex/Bugs_pre_410.tex
new file mode 100644
index 0000000000..a0cfe898bb
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Bugs_pre_410.tex
@@ -0,0 +1,6 @@
+\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}pre\_\allowbreak{}410}}\label{container-page-test-module-Bugs+u+pre+u+410}%
+\label{container-page-test-module-Bugs+u+pre+u+410-type-opt'}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt' = int option}\\
+\label{container-page-test-module-Bugs+u+pre+u+410-val-foo'}\ocamlcodefragment{\ocamltag{keyword}{val} foo' : ?bar:int \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Similar to \ocamlinlinecode{Bugs}, but the printed type of \ocamlinlinecode{\textasciitilde{}bar} should be \ocamlinlinecode{int}, not \ocamlinlinecode{'a}. This probably requires fixing in the compiler. See \href{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}\footnote{\url{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}}.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Class.empty_virtual'.tex b/test/generators/cases_pre408/latex/Class.empty_virtual'.tex
new file mode 100644
index 0000000000..539acacd8b
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Class.empty_virtual'.tex
@@ -0,0 +1,3 @@
+\section{Class \ocamlinlinecode{Class.\allowbreak{}empty\_\allowbreak{}virtual'}}\label{container-page-test-module-Class-class-empty+u+virtual'}%
+
+
diff --git a/test/latex/expect/test_package+ml/Class.mutually'.tex b/test/generators/cases_pre408/latex/Class.mutually'.tex
similarity index 50%
rename from test/latex/expect/test_package+ml/Class.mutually'.tex
rename to test/generators/cases_pre408/latex/Class.mutually'.tex
index 82792c2704..24a2f689e3 100644
--- a/test/latex/expect/test_package+ml/Class.mutually'.tex
+++ b/test/generators/cases_pre408/latex/Class.mutually'.tex
@@ -1,3 +1,3 @@
-\section{Class \ocamlinlinecode{Class.\allowbreak{}mutually'}}\label{package-test+u+package+++ml-module-Class-class-mutually'}%
+\section{Class \ocamlinlinecode{Class.\allowbreak{}mutually'}}\label{container-page-test-module-Class-class-mutually'}%
diff --git a/test/generators/cases_pre408/latex/Class.polymorphic'.tex b/test/generators/cases_pre408/latex/Class.polymorphic'.tex
new file mode 100644
index 0000000000..59293e3dce
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Class.polymorphic'.tex
@@ -0,0 +1,3 @@
+\section{Class \ocamlinlinecode{Class.\allowbreak{}polymorphic'}}\label{container-page-test-module-Class-class-polymorphic'}%
+
+
diff --git a/test/latex/expect/test_package+ml/Class.recursive'.tex b/test/generators/cases_pre408/latex/Class.recursive'.tex
similarity index 50%
rename from test/latex/expect/test_package+ml/Class.recursive'.tex
rename to test/generators/cases_pre408/latex/Class.recursive'.tex
index 395e5f9388..17bf7d2c96 100644
--- a/test/latex/expect/test_package+ml/Class.recursive'.tex
+++ b/test/generators/cases_pre408/latex/Class.recursive'.tex
@@ -1,3 +1,3 @@
-\section{Class \ocamlinlinecode{Class.\allowbreak{}recursive'}}\label{package-test+u+package+++ml-module-Class-class-recursive'}%
+\section{Class \ocamlinlinecode{Class.\allowbreak{}recursive'}}\label{container-page-test-module-Class-class-recursive'}%
diff --git a/test/generators/cases_pre408/latex/Class.tex b/test/generators/cases_pre408/latex/Class.tex
new file mode 100644
index 0000000000..e728201520
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Class.tex
@@ -0,0 +1,20 @@
+\section{Module \ocamlinlinecode{Class}}\label{container-page-test-module-Class}%
+\label{container-page-test-module-Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\
+\label{container-page-test-module-Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\
+\label{container-page-test-module-Class-class-type-empty+u+virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[container-page-test-module-Class-class-type-empty+u+virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Class-class-empty+u+virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[container-page-test-module-Class-class-empty+u+virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\\
+\label{container-page-test-module-Class-class-type-polymorphic}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} 'a \hyperref[container-page-test-module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Class-class-polymorphic'}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[container-page-test-module-Class-class-polymorphic']{\ocamlinlinecode{polymorphic'}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\\
+
+\input{test/Class.mutually'.tex}
+\input{test/Class.recursive'.tex}
+\input{test/Class.empty_virtual'.tex}
+\input{test/Class.polymorphic'.tex}
diff --git a/test/generators/cases_pre408/latex/External.tex b/test/generators/cases_pre408/latex/External.tex
new file mode 100644
index 0000000000..8021b64b4c
--- /dev/null
+++ b/test/generators/cases_pre408/latex/External.tex
@@ -0,0 +1,5 @@
+\section{Module \ocamlinlinecode{External}}\label{container-page-test-module-External}%
+\label{container-page-test-module-External-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Foo \emph{bar}.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Functor.F1.tex b/test/generators/cases_pre408/latex/Functor.F1.tex
new file mode 100644
index 0000000000..f6abd681c3
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor.F1.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Functor.\allowbreak{}F1}}\label{container-page-test-module-Functor-module-F1}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor-module-F1-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor-module-F1-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor-module-F1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Functor.F2.tex b/test/generators/cases_pre408/latex/Functor.F2.tex
new file mode 100644
index 0000000000..988eafa648
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor.F2.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Functor.\allowbreak{}F2}}\label{container-page-test-module-Functor-module-F2}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor-module-F2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor-module-F2-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor-module-F2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Functor.F3.tex b/test/generators/cases_pre408/latex/Functor.F3.tex
new file mode 100644
index 0000000000..e17833e77c
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor.F3.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Functor.\allowbreak{}F3}}\label{container-page-test-module-Functor-module-F3}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor-module-F3-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor-module-F3-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor-module-F3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Functor-module-F3-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Functor.F4.tex b/test/generators/cases_pre408/latex/Functor.F4.tex
new file mode 100644
index 0000000000..f37b786377
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor.F4.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Functor.\allowbreak{}F4}}\label{container-page-test-module-Functor-module-F4}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor-module-F4-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor-module-F4-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor-module-F4-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Functor.F5.tex b/test/generators/cases_pre408/latex/Functor.F5.tex
new file mode 100644
index 0000000000..d10dcc0b5e
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor.F5.tex
@@ -0,0 +1,6 @@
+\section{Module \ocamlinlinecode{Functor.\allowbreak{}F5}}\label{container-page-test-module-Functor-module-F5}%
+\subsection{Parameters\label{parameters}}%
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor-module-F5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Functor.tex b/test/generators/cases_pre408/latex/Functor.tex
new file mode 100644
index 0000000000..e93d8051fc
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor.tex
@@ -0,0 +1,23 @@
+\section{Module \ocamlinlinecode{Functor}}\label{container-page-test-module-Functor}%
+\label{container-page-test-module-Functor-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Functor-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor-module-type-S1-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-type-S1-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor-module-type-S1-argument-1-+u+-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsubsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor-module-type-S1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor-module-F1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F1]{\ocamlinlinecode{F1}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\
+\label{container-page-test-module-Functor-module-F2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F2]{\ocamlinlinecode{F2}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Functor-module-type-S-type-t]{\ocamlinlinecode{t}} = \hyperref[container-page-test-module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\
+\label{container-page-test-module-Functor-module-F3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F3]{\ocamlinlinecode{F3}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor-module-F4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F4]{\ocamlinlinecode{F4}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\
+\label{container-page-test-module-Functor-module-F5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor-module-F5]{\ocamlinlinecode{F5}}}\ocamlcodefragment{ () : \hyperref[container-page-test-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\
+
+\input{test/Functor.F1.tex}
+\input{test/Functor.F2.tex}
+\input{test/Functor.F3.tex}
+\input{test/Functor.F4.tex}
+\input{test/Functor.F5.tex}
diff --git a/test/generators/cases_pre408/latex/Functor2.X.tex b/test/generators/cases_pre408/latex/Functor2.X.tex
new file mode 100644
index 0000000000..302ca6e84e
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor2.X.tex
@@ -0,0 +1,14 @@
+\section{Module \ocamlinlinecode{Functor2.\allowbreak{}X}}\label{container-page-test-module-Functor2-module-X}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor2-module-X-argument-1-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor2-module-X-argument-1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor2-module-X-argument-1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor2-module-X-argument-2-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor2-module-X-argument-2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor2-module-X-argument-2-Z-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor2-module-X-type-y+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} y\_\allowbreak{}t = \hyperref[container-page-test-module-Functor2-module-X-argument-1-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\
+\label{container-page-test-module-Functor2-module-X-type-z+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} z\_\allowbreak{}t = \hyperref[container-page-test-module-Functor2-module-X-argument-2-Z-type-t]{\ocamlinlinecode{Z.\allowbreak{}t}}}\\
+\label{container-page-test-module-Functor2-module-X-type-x+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} x\_\allowbreak{}t = \hyperref[container-page-test-module-Functor2-module-X-type-y+u+t]{\ocamlinlinecode{y\_\allowbreak{}t}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Functor2.tex b/test/generators/cases_pre408/latex/Functor2.tex
new file mode 100644
index 0000000000..cd85d0cd8e
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Functor2.tex
@@ -0,0 +1,20 @@
+\section{Module \ocamlinlinecode{Functor2}}\label{container-page-test-module-Functor2}%
+\label{container-page-test-module-Functor2-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Functor2-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor2-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor2-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Functor2-module-X-argument-1-Y]{\ocamlinlinecode{Y}} : \hyperref[container-page-test-module-Functor2-module-type-S]{\ocamlinlinecode{S}}) (\hyperref[container-page-test-module-Functor2-module-X-argument-2-Z]{\ocamlinlinecode{Z}} : \hyperref[container-page-test-module-Functor2-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor2-module-type-XF}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Functor2-module-type-XF]{\ocamlinlinecode{XF}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Functor2-module-type-XF-argument-1-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor2-module-type-XF-argument-1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor2-module-type-XF-argument-1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Functor2-module-type-XF-argument-2-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Functor2-module-type-XF-argument-2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Functor2-module-type-XF-argument-2-Z-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsubsection{Signature\label{signature}}%
+\label{container-page-test-module-Functor2-module-type-XF-type-y+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} y\_\allowbreak{}t = \hyperref[container-page-test-module-Functor2-module-type-XF-argument-1-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\
+\label{container-page-test-module-Functor2-module-type-XF-type-z+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} z\_\allowbreak{}t = \hyperref[container-page-test-module-Functor2-module-type-XF-argument-2-Z-type-t]{\ocamlinlinecode{Z.\allowbreak{}t}}}\\
+\label{container-page-test-module-Functor2-module-type-XF-type-x+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} x\_\allowbreak{}t = \hyperref[container-page-test-module-Functor2-module-type-XF-type-y+u+t]{\ocamlinlinecode{y\_\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+
+\input{test/Functor2.X.tex}
diff --git a/test/generators/cases_pre408/latex/Include.tex b/test/generators/cases_pre408/latex/Include.tex
new file mode 100644
index 0000000000..adc7ee609a
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Include.tex
@@ -0,0 +1,29 @@
+\section{Module \ocamlinlinecode{Include}}\label{container-page-test-module-Include}%
+\label{container-page-test-module-Include-module-type-Not+u+inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include-module-type-Not+u+inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include-module-type-Not+u+inlined-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Not+u+inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}\label{container-page-test-module-Include-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Include-module-type-Inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include-module-type-Inlined-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}\label{container-page-test-module-Include-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+closed}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+closed-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}\label{container-page-test-module-Include-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\
+\label{container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+opened}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+opened-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}\label{container-page-test-module-Include-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\
+\label{container-page-test-module-Include-module-type-Inherent+u+Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include-module-type-Inherent+u+Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test-module-Include-type-t]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{container-page-test-module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test-module-Include-type-t]{\ocamlinlinecode{t}}}\\
+\label{container-page-test-module-Include-module-type-Dorminant+u+Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include-module-type-Dorminant+u+Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{container-page-test-module-Include-module-type-Dorminant+u+Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test-module-Include-type-t]{\ocamlinlinecode{t}}}\\
+\label{container-page-test-module-Include-module-type-Dorminant+u+Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test-module-Include-type-u]{\ocamlinlinecode{u}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Dorminant+u+Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{container-page-test-module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test-module-Include-type-t]{\ocamlinlinecode{t}}}\\
+\label{container-page-test-module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test-module-Include-type-u]{\ocamlinlinecode{u}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Include2.tex b/test/generators/cases_pre408/latex/Include2.tex
new file mode 100644
index 0000000000..e529d4521f
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Include2.tex
@@ -0,0 +1,21 @@
+\section{Module \ocamlinlinecode{Include2}}\label{container-page-test-module-Include2}%
+\label{container-page-test-module-Include2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Include2-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include2-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Comment about X that should not appear when including X below.\end{ocamlindent}%
+\medbreak
+\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[container-page-test-module-Include2-module-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{end}Comment about X that should not appear when including X below.
+
+\label{container-page-test-module-Include2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
+\label{container-page-test-module-Include2-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Include2-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include2-module-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment of Y.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Include2-module-Y+u+include+u+synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Include2-module-Y+u+include+u+synopsis]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[container-page-test-module-Include2-module-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{container-page-test-module-Include2-module-Y+u+include+u+synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Include2-module-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}The \ocamlinlinecode{include Y} below should have the synopsis from \ocamlinlinecode{Y}'s top-comment attached to it.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Include2-module-Y+u+include+u+doc}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Include2-module-Y+u+include+u+doc]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}doc}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}Doc attached to \ocamlinlinecode{include Y}. \ocamlinlinecode{Y}'s top-comment shouldn't appear here.\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[container-page-test-module-Include2-module-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{container-page-test-module-Include2-module-Y+u+include+u+doc-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Include2-module-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Include_sections.tex b/test/generators/cases_pre408/latex/Include_sections.tex
new file mode 100644
index 0000000000..8a8df5536e
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Include_sections.tex
@@ -0,0 +1,71 @@
+\section{Module \ocamlinlinecode{Include\_\allowbreak{}sections}}\label{container-page-test-module-Include+u+sections}%
+\label{container-page-test-module-Include+u+sections-module-type-Something}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Include+u+sections-module-type-Something-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
+\subsubsection{Something 1\label{something-1}}%
+foo
+
+\label{container-page-test-module-Include+u+sections-module-type-Something-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
+\subsubsection{Something 2\label{something-2}}%
+\label{container-page-test-module-Include+u+sections-module-type-Something-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
+\medbreak
+\subsubsection{Something 1-bis\label{something-1-bis}}%
+Some text.
+
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A module type.\end{ocamlindent}%
+\medbreak
+Let's include \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{container-page-test-module-Include+u+sections-module-type-Something}]} once
+
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
+\subsection{Something 1\label{something-1}}%
+foo
+
+\label{container-page-test-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
+\subsubsection{Something 2\label{something-2}}%
+\label{container-page-test-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
+\medbreak
+\subsection{Something 1-bis\label{something-1-bis}}%
+Some text.
+
+\subsection{Second include\label{second-include}}%
+Let's include \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{container-page-test-module-Include+u+sections-module-type-Something}]} a second time: the heading level should be shift here.
+
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
+\subsection{Something 1\label{something-1}}%
+foo
+
+\label{container-page-test-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
+\subsubsection{Something 2\label{something-2}}%
+\label{container-page-test-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
+\medbreak
+\subsection{Something 1-bis\label{something-1-bis}}%
+Some text.
+
+\subsubsection{Third include\label{third-include}}%
+Shifted some more.
+
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
+\subsection{Something 1\label{something-1}}%
+foo
+
+\label{container-page-test-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
+\subsubsection{Something 2\label{something-2}}%
+\label{container-page-test-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
+\medbreak
+\subsection{Something 1-bis\label{something-1-bis}}%
+Some text.
+
+And let's include it again, but without inlining it this time: the ToC shouldn't grow.
+
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
+\subsection{Something 1\label{something-1}}%
+foo
+
+\label{container-page-test-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
+\subsubsection{Something 2\label{something-2}}%
+\label{container-page-test-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
+\medbreak
+\subsection{Something 1-bis\label{something-1-bis}}%
+Some text.
+
+
+
diff --git a/test/generators/cases_pre408/latex/Interlude.tex b/test/generators/cases_pre408/latex/Interlude.tex
new file mode 100644
index 0000000000..3d88672981
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Interlude.tex
@@ -0,0 +1,22 @@
+\section{Module \ocamlinlinecode{Interlude}}\label{container-page-test-module-Interlude}%
+This is the comment associated to the module.
+
+Some separate stray text at the top of the module.
+
+\label{container-page-test-module-Interlude-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Foo.\end{ocamlindent}%
+\medbreak
+Some stray text that is not associated with any signature item.
+
+It has multiple paragraphs.
+
+A separate block of stray text, adjacent to the preceding one.
+
+\label{container-page-test-module-Interlude-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}Bar.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Interlude-val-multiple}\ocamlcodefragment{\ocamltag{keyword}{val} multiple : unit}\\
+\label{container-page-test-module-Interlude-val-signature}\ocamlcodefragment{\ocamltag{keyword}{val} signature : unit}\\
+\label{container-page-test-module-Interlude-val-items}\ocamlcodefragment{\ocamltag{keyword}{val} items : unit}\\
+Stray text at the bottom of the module.
+
+
+
diff --git a/test/latex/expect/test_package+ml/Markup.tex b/test/generators/cases_pre408/latex/Markup.tex
similarity index 70%
rename from test/latex/expect/test_package+ml/Markup.tex
rename to test/generators/cases_pre408/latex/Markup.tex
index ad93817785..c6cfa88925 100644
--- a/test/latex/expect/test_package+ml/Markup.tex
+++ b/test/generators/cases_pre408/latex/Markup.tex
@@ -1,4 +1,4 @@
-\section{Module \ocamlinlinecode{Markup}}\label{container-page-test+u+package+++ml-module-Markup}%
+\section{Module \ocamlinlinecode{Markup}}\label{container-page-test-module-Markup}%
Here, we test the rendering of comment markup.
\subsection{Sections\label{sections}}%
@@ -13,7 +13,7 @@ \subsubsection{Sub-subsection headings\label{sub-subsection-headings}}%
but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files.
\subsubsection{Anchors\label{anchors}}%
-Sections can have attached \hyperref[container-page-test+u+package+++ml-module-Markup-anchors]{\ocamlinlinecode{Anchors}[p\pageref*{container-page-test+u+package+++ml-module-Markup-anchors}]}, and it is possible to \hyperref[container-page-test+u+package+++ml-module-Markup-anchors]{\ocamlinlinecode{link}[p\pageref*{container-page-test+u+package+++ml-module-Markup-anchors}]} to them. Links to section headers should not be set in source code style.
+Sections can have attached \hyperref[container-page-test-module-Markup-anchors]{\ocamlinlinecode{Anchors}[p\pageref*{container-page-test-module-Markup-anchors}]}, and it is possible to \hyperref[container-page-test-module-Markup-anchors]{\ocamlinlinecode{link}[p\pageref*{container-page-test-module-Markup-anchors}]} to them. Links to section headers should not be set in source code style.
\subsubsection{Paragraph\label{paragraph}}%
Individual paragraphs can have a heading.
@@ -37,7 +37,7 @@ \subsection{Styling\label{styling}}%
\subsection{Links and references\label{links-and-references}}%
This is a \href{\#}{link}\footnote{\url{\#}}. It sends you to the top of this page. Links can have markup inside them: \href{\#}{\bold{bold}}\footnote{\url{\#}}, \href{\#}{\emph{italics}}\footnote{\url{\#}}, \href{\#}{\emph{emphasis}}\footnote{\url{\#}}, \href{\#}{super\textsuperscript{script}}\footnote{\url{\#}}, \href{\#}{sub\textsubscript{script}}\footnote{\url{\#}}, and \href{\#}{\ocamlinlinecode{code}}\footnote{\url{\#}}. Links can also be nested \emph{\href{\#}{inside}\footnote{\url{\#}}} markup. Links cannot be nested inside each other. This link has no replacement text: \href{\#}{\#}\footnote{\url{\#}}. The text is filled in by odoc. This is a shorthand link: \href{\#}{\#}\footnote{\url{\#}}. The text is also filled in by odoc in this case.
-This is a reference to \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}. References can have replacement text: \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{the value foo}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}. Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\bold{bold}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\emph{italic}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\emph{emphasis}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{super\textsuperscript{script}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{sub\textsubscript{script}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}, and \hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{code}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}. It's also possible to surround a reference in a style: \bold{\hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}}. References can't be nested inside references, and links and references can't be nested inside each other.
+This is a reference to \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{container-page-test-module-Markup-val-foo}]}. References can have replacement text: \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{the value foo}[p\pageref*{container-page-test-module-Markup-val-foo}]}. Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\bold{bold}}[p\pageref*{container-page-test-module-Markup-val-foo}]}, \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\emph{italic}}[p\pageref*{container-page-test-module-Markup-val-foo}]}, \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\emph{emphasis}}[p\pageref*{container-page-test-module-Markup-val-foo}]}, \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{super\textsuperscript{script}}[p\pageref*{container-page-test-module-Markup-val-foo}]}, \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{sub\textsubscript{script}}[p\pageref*{container-page-test-module-Markup-val-foo}]}, and \hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{code}}[p\pageref*{container-page-test-module-Markup-val-foo}]}. It's also possible to surround a reference in a style: \bold{\hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{container-page-test-module-Markup-val-foo}]}}. References can't be nested inside references, and links and references can't be nested inside each other.
\subsection{Preformatted text\label{preformatted-text}}%
This is a code block:\medbreak
@@ -74,7 +74,7 @@ \subsection{Lists\label{lists}}%
\begin{itemize}\item{\begin{itemize}\item{lists}%
\item{can be nested}%
\item{and can include references}%
-\item{\hyperref[container-page-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{container-page-test+u+package+++ml-module-Markup-val-foo}]}}\end{itemize}%
+\item{\hyperref[container-page-test-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{container-page-test-module-Markup-val-foo}]}}\end{itemize}%
}\end{itemize}%
\subsection{Unicode\label{unicode}}%
The parser supports any ASCII-compatible encoding, in particuλar UTF-8.
@@ -143,7 +143,7 @@ \subsection{Tags\label{tags}}%
\begin{description}\kern-\topsep
\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
\item[{version}]{-1}\end{description}%
-\label{container-page-test+u+package+++ml-module-Markup-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Comments in structure items \bold{support} \emph{markup}, t\textsuperscript{o}\textsubscript{o}.\end{ocamlindent}%
+\label{container-page-test-module-Markup-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Comments in structure items \bold{support} \emph{markup}, t\textsuperscript{o}\textsubscript{o}.\end{ocamlindent}%
\medbreak
diff --git a/test/generators/cases_pre408/latex/Module.tex b/test/generators/cases_pre408/latex/Module.tex
new file mode 100644
index 0000000000..3d4f8773fd
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Module.tex
@@ -0,0 +1,75 @@
+\section{Module \ocamlinlinecode{Module}}\label{container-page-test-module-Module}%
+Foo.
+
+\label{container-page-test-module-Module-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See \href{https://caml.inria.fr/mantis/view.php?id=7701}{https://caml.inria.fr/mantis/view.php?id=7701}\footnote{\url{https://caml.inria.fr/mantis/view.php?id=7701}}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Module-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Module-module-type-S-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\label{container-page-test-module-Module-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-type-S-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S1}\\
+\label{container-page-test-module-Module-module-type-S2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S2]{\ocamlinlinecode{S2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Module-module-type-S2-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S2-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S2-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\label{container-page-test-module-Module-module-type-S2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-type-S2-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S3}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S3]{\ocamlinlinecode{S3}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
+\label{container-page-test-module-Module-module-type-S3-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = string}\\
+\label{container-page-test-module-Module-module-type-S3-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S3-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\label{container-page-test-module-Module-module-type-S3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-type-S3-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S4}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S4]{\ocamlinlinecode{S4}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S4-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S4-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S4-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\label{container-page-test-module-Module-module-type-S4-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-type-S4-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S5}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S5]{\ocamlinlinecode{S5}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Module-module-type-S5-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S5-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\label{container-page-test-module-Module-module-type-S5-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-type-S5-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-type-result}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) result}\\
+\label{container-page-test-module-Module-module-type-S6}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S6]{\ocamlinlinecode{S6}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S6-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Module-module-type-S6-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S6-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S6-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-type-S6-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S7}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S7]{\ocamlinlinecode{S7}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S7-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Module-module-type-S7-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S7-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S7-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\label{container-page-test-module-Module-module-type-S7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[container-page-test-module-Module-module-M']{\ocamlinlinecode{M'}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S8]{\ocamlinlinecode{S8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Module-module-type-S8-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Module-module-type-S8-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\label{container-page-test-module-Module-module-type-S8-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
+\label{container-page-test-module-Module-module-type-S8-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-type-S9}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Module-module-type-S9]{\ocamlinlinecode{S9}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-Mutually}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-Mutually]{\ocamlinlinecode{Mutually}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Module-module-Recursive}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Module-module-Recursive]{\ocamlinlinecode{Recursive}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Nested.F.tex b/test/generators/cases_pre408/latex/Nested.F.tex
new file mode 100644
index 0000000000..838e50ce93
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Nested.F.tex
@@ -0,0 +1,25 @@
+\section{Module \ocamlinlinecode{Nested.\allowbreak{}F}}\label{container-page-test-module-Nested-module-F}%
+This is a functor F.
+
+Some additional comments.
+
+\subsection{Type\label{type}}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Nested-module-F-argument-1-Arg1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
+\label{container-page-test-module-Nested-module-F-argument-1-Arg1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
+\medbreak
+\subsubsection{Values\label{values}}%
+\label{container-page-test-module-Nested-module-F-argument-1-Arg1-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[container-page-test-module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Nested-module-F-argument-2-Arg2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
+\label{container-page-test-module-Nested-module-F-argument-2-Arg2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Nested-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{Arg1.\allowbreak{}t}} * \hyperref[container-page-test-module-Nested-module-F-argument-2-Arg2-type-t]{\ocamlinlinecode{Arg2.\allowbreak{}t}}}\begin{ocamlindent}Some type.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Nested.inherits.tex b/test/generators/cases_pre408/latex/Nested.inherits.tex
new file mode 100644
index 0000000000..361a92e9dd
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Nested.inherits.tex
@@ -0,0 +1,4 @@
+\section{Class \ocamlinlinecode{Nested.\allowbreak{}inherits}}\label{container-page-test-module-Nested-class-inherits}%
+\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[container-page-test-module-Nested-class-z]{\ocamlinlinecode{z}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Nested.tex b/test/generators/cases_pre408/latex/Nested.tex
new file mode 100644
index 0000000000..38992a5568
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Nested.tex
@@ -0,0 +1,34 @@
+\section{Module \ocamlinlinecode{Nested}}\label{container-page-test-module-Nested}%
+This comment needs to be here before \#235 is fixed.
+
+\subsection{Module\label{module}}%
+\label{container-page-test-module-Nested-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Nested-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
+\label{container-page-test-module-Nested-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
+\medbreak
+\subsubsection{Values\label{values}}%
+\label{container-page-test-module-Nested-module-X-val-x}\ocamlcodefragment{\ocamltag{keyword}{val} x : \hyperref[container-page-test-module-Nested-module-X-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of x.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module X.\end{ocamlindent}%
+\medbreak
+\subsection{Module type\label{module-type}}%
+\label{container-page-test-module-Nested-module-type-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Nested-module-type-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
+\label{container-page-test-module-Nested-module-type-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
+\medbreak
+\subsubsection{Values\label{values}}%
+\label{container-page-test-module-Nested-module-type-Y-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[container-page-test-module-Nested-module-type-Y-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module type Y.\end{ocamlindent}%
+\medbreak
+\subsection{Functor\label{functor}}%
+\label{container-page-test-module-Nested-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Nested-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}} : \hyperref[container-page-test-module-Nested-module-type-Y]{\ocamlinlinecode{Y}}) (\hyperref[container-page-test-module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is a functor F.\end{ocamlindent}%
+\medbreak
+\subsection{Class\label{class}}%
+\label{container-page-test-module-Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[container-page-test-module-Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[container-page-test-module-Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+
+\input{test/Nested.F.tex}
+\input{test/Nested.z.tex}
+\input{test/Nested.inherits.tex}
diff --git a/test/generators/cases_pre408/latex/Nested.z.tex b/test/generators/cases_pre408/latex/Nested.z.tex
new file mode 100644
index 0000000000..db7e48d1a6
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Nested.z.tex
@@ -0,0 +1,14 @@
+\section{Class \ocamlinlinecode{Nested.\allowbreak{}z}}\label{container-page-test-module-Nested-class-z}%
+This is class z.
+
+Some additional comments.
+
+\label{container-page-test-module-Nested-class-z-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : int}\begin{ocamlindent}Some value.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Nested-class-z-val-y'}\ocamlcodefragment{\ocamltag{keyword}{val} \ocamltag{keyword}{mutable} \ocamltag{keyword}{virtual} y' : int}\\
+\subsection{Methods\label{methods}}%
+\label{container-page-test-module-Nested-class-z-method-z}\ocamlcodefragment{\ocamltag{keyword}{method} z : int}\begin{ocamlindent}Some method.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Nested-class-z-method-z'}\ocamlcodefragment{\ocamltag{keyword}{method} \ocamltag{keyword}{private} \ocamltag{keyword}{virtual} z' : int}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep12.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep12.tex
new file mode 100644
index 0000000000..f6df514666
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep12.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep12}}\label{container-page-test-module-Ocamlary-module-Dep12}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-Dep12-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep12-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep12-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-Dep12-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[container-page-test-module-Ocamlary-module-Dep12-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep13.c.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep13.c.tex
new file mode 100644
index 0000000000..3af2cfc0e9
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep13.c.tex
@@ -0,0 +1,4 @@
+\section{Class \ocamlinlinecode{Dep13.\allowbreak{}c}}\label{container-page-test-module-Ocamlary-module-Dep13-class-c}%
+\label{container-page-test-module-Ocamlary-module-Dep13-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep13.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep13.tex
new file mode 100644
index 0000000000..873fa0f5de
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep13.tex
@@ -0,0 +1,4 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep13}}\label{container-page-test-module-Ocamlary-module-Dep13}%
+\label{container-page-test-module-Ocamlary-module-Dep13-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Ocamlary-module-Dep13-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+
+\input{test/Ocamlary.Dep13.c.tex}
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep2.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep2.tex
new file mode 100644
index 0000000000..93232b462f
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep2.tex
@@ -0,0 +1,15 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep2}}\label{container-page-test-module-Ocamlary-module-Dep2}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\
+\label{container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg-module-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-Dep2-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep2-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep2-module-A-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep2-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[container-page-test-module-Ocamlary-module-Dep2-module-A-module-Y]{\ocamlinlinecode{A.\allowbreak{}Y}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep5.Z.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep5.Z.tex
new file mode 100644
index 0000000000..4d6e8b09c7
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep5.Z.tex
@@ -0,0 +1,5 @@
+\section{Module \ocamlinlinecode{Dep5.\allowbreak{}Z}}\label{container-page-test-module-Ocamlary-module-Dep5-module-Z}%
+\label{container-page-test-module-Ocamlary-module-Dep5-module-Z-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{Arg.\allowbreak{}T}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep5-module-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y = \hyperref[container-page-test-module-Ocamlary-module-Dep3]{\ocamlinlinecode{Dep3}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep5.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep5.tex
new file mode 100644
index 0000000000..46120a8c7f
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep5.tex
@@ -0,0 +1,15 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep5}}\label{container-page-test-module-Ocamlary-module-Dep5}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\
+\label{container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-Dep5-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep5-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-Y]{\ocamlinlinecode{Y}} = \hyperref[container-page-test-module-Ocamlary-module-Dep3]{\ocamlinlinecode{Dep3}}}\\
+
+\input{test/Ocamlary.Dep5.Z.tex}
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep7.M.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep7.M.tex
new file mode 100644
index 0000000000..8b035e81c3
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep7.M.tex
@@ -0,0 +1,5 @@
+\section{Module \ocamlinlinecode{Dep7.\allowbreak{}M}}\label{container-page-test-module-Ocamlary-module-Dep7-module-M}%
+\label{container-page-test-module-Ocamlary-module-Dep7-module-M-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep7-module-M-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[container-page-test-module-Ocamlary-module-Dep7-module-M-module-type-R]{\ocamlinlinecode{R}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep7.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep7.tex
new file mode 100644
index 0000000000..676bc98b88
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep7.tex
@@ -0,0 +1,17 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep7}}\label{container-page-test-module-Ocamlary-module-Dep7}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\
+\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T-module-type-R]{\ocamlinlinecode{R}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-X-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-X-module-type-R]{\ocamlinlinecode{R}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-Dep7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep7-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T]{\ocamlinlinecode{Arg.\allowbreak{}T}}}\\
+
+\input{test/Ocamlary.Dep7.M.tex}
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Dep9.tex b/test/generators/cases_pre408/latex/Ocamlary.Dep9.tex
new file mode 100644
index 0000000000..0df6d95e9a
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Dep9.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep9}}\label{container-page-test-module-Ocamlary-module-Dep9}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-Dep9-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep9-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep9-argument-1-X-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-Dep9-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[container-page-test-module-Ocamlary-module-Dep9-argument-1-X-module-type-T]{\ocamlinlinecode{X.\allowbreak{}T}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.FunctorTypeOf.tex b/test/generators/cases_pre408/latex/Ocamlary.FunctorTypeOf.tex
new file mode 100644
index 0000000000..fe42ae97fe
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.FunctorTypeOf.tex
@@ -0,0 +1,36 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}FunctorTypeOf}}\label{container-page-test-module-Ocamlary-module-FunctorTypeOf}%
+This comment is for \ocamlinlinecode{FunctorTypeOf}.
+
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection]{\ocamlinlinecode{Collection}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-collection]{\ocamlinlinecode{Collection.\allowbreak{}collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.ModuleWithSignature.tex b/test/generators/cases_pre408/latex/Ocamlary.ModuleWithSignature.tex
new file mode 100644
index 0000000000..db44ab8d2f
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.ModuleWithSignature.tex
@@ -0,0 +1,5 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}ModuleWithSignature}}\label{container-page-test-module-Ocamlary-module-ModuleWithSignature}%
+A plain module of a signature of \hyperref[container-page-test-module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{container-page-test-module-Ocamlary-module-type-EmptySig}]} (reference)
+
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.ModuleWithSignatureAlias.tex b/test/generators/cases_pre408/latex/Ocamlary.ModuleWithSignatureAlias.tex
new file mode 100644
index 0000000000..c0e73089de
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.ModuleWithSignatureAlias.tex
@@ -0,0 +1,10 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}ModuleWithSignatureAlias}}\label{container-page-test-module-Ocamlary-module-ModuleWithSignatureAlias}%
+A plain module with an alias signature
+
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{deprecated}]{I don't like this element any more.
+
+}\end{description}%
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.Recollection.tex b/test/generators/cases_pre408/latex/Ocamlary.Recollection.tex
new file mode 100644
index 0000000000..909ede9220
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.Recollection.tex
@@ -0,0 +1,57 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Recollection}}\label{container-page-test-module-Ocamlary-module-Recollection}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-Recollection-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-element]{\ocamlinlinecode{C.\allowbreak{}element}} list}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{C.\allowbreak{}collection}}}\\
+\label{container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-Recollection-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Recollection-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Recollection-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.With3.N.tex b/test/generators/cases_pre408/latex/Ocamlary.With3.N.tex
new file mode 100644
index 0000000000..b7a9499297
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.With3.N.tex
@@ -0,0 +1,4 @@
+\section{Module \ocamlinlinecode{With3.\allowbreak{}N}}\label{container-page-test-module-Ocamlary-module-With3-module-N}%
+\label{container-page-test-module-Ocamlary-module-With3-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.With3.tex b/test/generators/cases_pre408/latex/Ocamlary.With3.tex
new file mode 100644
index 0000000000..f67df784aa
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.With3.tex
@@ -0,0 +1,5 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With3}}\label{container-page-test-module-Ocamlary-module-With3}%
+\label{container-page-test-module-Ocamlary-module-With3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[container-page-test-module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\\
+\label{container-page-test-module-Ocamlary-module-With3-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With3-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-With2-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\
+
+\input{test/Ocamlary.With3.N.tex}
diff --git a/test/generators/cases_pre408/latex/Ocamlary.With4.N.tex b/test/generators/cases_pre408/latex/Ocamlary.With4.N.tex
new file mode 100644
index 0000000000..87c35d68af
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.With4.N.tex
@@ -0,0 +1,4 @@
+\section{Module \ocamlinlinecode{With4.\allowbreak{}N}}\label{container-page-test-module-Ocamlary-module-With4-module-N}%
+\label{container-page-test-module-Ocamlary-module-With4-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.With4.tex b/test/generators/cases_pre408/latex/Ocamlary.With4.tex
new file mode 100644
index 0000000000..7821c6b08b
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.With4.tex
@@ -0,0 +1,4 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With4}}\label{container-page-test-module-Ocamlary-module-With4}%
+\label{container-page-test-module-Ocamlary-module-With4-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With4-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-With2-module-type-S]{\ocamlinlinecode{With2.\allowbreak{}S}}}\\
+
+\input{test/Ocamlary.With4.N.tex}
diff --git a/test/generators/cases_pre408/latex/Ocamlary.With7.tex b/test/generators/cases_pre408/latex/Ocamlary.With7.tex
new file mode 100644
index 0000000000..e58c0d2260
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.With7.tex
@@ -0,0 +1,9 @@
+\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With7}}\label{container-page-test-module-Ocamlary-module-With7}%
+\subsection{Parameters\label{parameters}}%
+\label{container-page-test-module-Ocamlary-module-With7-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With7-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With7-argument-1-X-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsection{Signature\label{signature}}%
+\label{container-page-test-module-Ocamlary-module-With7-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[container-page-test-module-Ocamlary-module-With7-argument-1-X-module-type-T]{\ocamlinlinecode{X.\allowbreak{}T}}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.empty_class.tex b/test/generators/cases_pre408/latex/Ocamlary.empty_class.tex
new file mode 100644
index 0000000000..f2a6a038a0
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.empty_class.tex
@@ -0,0 +1,3 @@
+\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}empty\_\allowbreak{}class}}\label{container-page-test-module-Ocamlary-class-empty+u+class}%
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.one_method_class.tex b/test/generators/cases_pre408/latex/Ocamlary.one_method_class.tex
new file mode 100644
index 0000000000..c5eda57ea1
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.one_method_class.tex
@@ -0,0 +1,4 @@
+\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}one\_\allowbreak{}method\_\allowbreak{}class}}\label{container-page-test-module-Ocamlary-class-one+u+method+u+class}%
+\label{container-page-test-module-Ocamlary-class-one+u+method+u+class-method-go}\ocamlcodefragment{\ocamltag{keyword}{method} go : unit}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.param_class.tex b/test/generators/cases_pre408/latex/Ocamlary.param_class.tex
new file mode 100644
index 0000000000..f7e2376c9b
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.param_class.tex
@@ -0,0 +1,4 @@
+\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}param\_\allowbreak{}class}}\label{container-page-test-module-Ocamlary-class-param+u+class}%
+\label{container-page-test-module-Ocamlary-class-param+u+class-method-v}\ocamlcodefragment{\ocamltag{keyword}{method} v : \ocamltag{type-var}{'a}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Ocamlary.tex b/test/generators/cases_pre408/latex/Ocamlary.tex
new file mode 100644
index 0000000000..c079517ed6
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.tex
@@ -0,0 +1,970 @@
+\section{Module \ocamlinlinecode{Ocamlary}}\label{container-page-test-module-Ocamlary}%
+This is an \emph{interface} with \bold{all} of the \emph{module system} features. This documentation demonstrates:
+
+\begin{itemize}\item{comment formatting}%
+\item{unassociated comments}%
+\item{documentation sections}%
+\item{module system documentation including
+
+\begin{enumerate}\item{submodules}%
+\item{module aliases}%
+\item{module types}%
+\item{module type aliases}%
+\item{modules with signatures}%
+\item{modules with aliased signatures}\end{enumerate}%
+}\end{itemize}%
+A numbered list:
+
+\begin{enumerate}\item{3}%
+\item{2}%
+\item{1}\end{enumerate}%
+David Sheets is the author.
+
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{author}]{David Sheets}\end{description}%
+You may find more information about this HTML documentation renderer at \href{https://github.com/dsheets/ocamlary}{github.com/dsheets/ocamlary}\footnote{\url{https://github.com/dsheets/ocamlary}}.
+
+This is some verbatim text:
+
+\begin{verbatim}verbatim\end{verbatim}%
+This is some verbatim text:
+
+\begin{verbatim}[][df[]]}}\end{verbatim}%
+Here is some raw LaTeX: $e^{i\pi} = -1$
+
+Here is an index table of \ocamlinlinecode{Empty} modules:
+
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{\hyperref[container-page-test-module-Ocamlary-module-Empty]{\ocamlinlinecode{\ocamlinlinecode{Empty}}[p\pageref*{container-page-test-module-Ocamlary-module-Empty}]}}]{A plain, empty module}%
+\item[{\hyperref[container-page-test-module-Ocamlary-module-Empty]{\ocamlinlinecode{\ocamlinlinecode{EmptyAlias}}[p\pageref*{container-page-test-module-Ocamlary-module-Empty}]}}]{A plain module alias of \ocamlinlinecode{Empty}}\end{description}%
+Here is a table of links to indexes: \ocamlinlinecode{indexlist}
+
+Here is some superscript: x\textsuperscript{2}
+
+Here is some subscript: x\textsubscript{0}
+
+Here are some escaped brackets: \{ [ @ ] \}
+
+Here is some \emph{emphasis} \ocamlinlinecode{followed by code}.
+
+An unassociated comment
+
+\subsection{Level 1\label{level-1}}%
+\subsubsection{Level 2\label{level-2}}%
+\subsubsection{Level 3\label{level-3}}%
+\subsubsection{Level 4\label{level-4}}%
+\subsubsection{Basic module stuff\label{basic-module-stuff}}%
+\label{container-page-test-module-Ocamlary-module-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A plain, empty module\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-Empty-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}An ambiguous, misnamed module type\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-MissingComment}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-MissingComment]{\ocamlinlinecode{MissingComment}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-MissingComment-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}An ambiguous, misnamed module type\end{ocamlindent}%
+\medbreak
+\subsection{Section 9000\label{s9000}}%
+\label{container-page-test-module-Ocamlary-module-EmptyAlias}\ocamlcodefragment{\ocamltag{keyword}{module} EmptyAlias = \hyperref[container-page-test-module-Ocamlary-module-Empty]{\ocamlinlinecode{Empty}}}\begin{ocamlindent}A plain module alias of \ocamlinlinecode{Empty}\end{ocamlindent}%
+\medbreak
+\subsubsection{EmptySig\label{emptySig}}%
+\label{container-page-test-module-Ocamlary-module-type-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A plain, empty module signature\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-EmptySigAlias}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-EmptySigAlias]{\ocamlinlinecode{EmptySigAlias}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A plain, empty module signature alias of\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-ModuleWithSignature}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-ModuleWithSignature]{\ocamlinlinecode{ModuleWithSignature}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\begin{ocamlindent}A plain module of a signature of \hyperref[container-page-test-module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{container-page-test-module-Ocamlary-module-type-EmptySig}]} (reference)\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-ModuleWithSignatureAlias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-ModuleWithSignatureAlias]{\ocamlinlinecode{ModuleWithSignatureAlias}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-type-EmptySigAlias]{\ocamlinlinecode{EmptySigAlias}}}\begin{ocamlindent}A plain module with an alias signature\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-One}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-One]{\ocamlinlinecode{One}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-One-type-one}\ocamlcodefragment{\ocamltag{keyword}{type} one}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-SigForMod}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SigForMod]{\ocamlinlinecode{SigForMod}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-SigForMod-module-Inner}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-SigForMod-module-Inner]{\ocamlinlinecode{Inner}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-SigForMod-module-Inner-module-type-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SigForMod-module-Inner-module-type-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}There's a signature in a module in this signature.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-SuperSig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig]{\ocamlinlinecode{SuperSig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigA]{\ocamlinlinecode{SubSigA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{A Labeled Section Header Inside of a Signature\label{subSig}}%
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod]{\ocamlinlinecode{SubSigAMod}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod-type-sub+u+sig+u+a+u+mod}\ocamlcodefragment{\ocamltag{keyword}{type} sub\_\allowbreak{}sig\_\allowbreak{}a\_\allowbreak{}mod}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigB]{\ocamlinlinecode{SubSigB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Another Labeled Section Header Inside of a Signature\label{subSig}}%
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SubSigB-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-EmptySig-type-not+u+actually+u+empty}\ocamlcodefragment{\ocamltag{keyword}{type} not\_\allowbreak{}actually\_\allowbreak{}empty}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-One}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-One]{\ocamlinlinecode{One}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-One-type-two}\ocamlcodefragment{\ocamltag{keyword}{type} two}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SuperSig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-SuperSig]{\ocamlinlinecode{SuperSig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+For a good time, see \ocamlinlinecode{SuperSig}.SubSigA.subSig or \ocamlinlinecode{SuperSig}.SubSigB.subSig or \hyperref[container-page-test-module-Ocamlary-module-type-SuperSig-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{SuperSig.\allowbreak{}EmptySig}}[p\pageref*{container-page-test-module-Ocamlary-module-type-SuperSig-module-type-EmptySig}]}. Section \hyperref[container-page-test-module-Ocamlary-s9000]{\ocamlinlinecode{Section 9000}[p\pageref*{container-page-test-module-Ocamlary-s9000}]} is also interesting. \hyperref[container-page-test-module-Ocamlary-emptySig]{\ocamlinlinecode{EmptySig}[p\pageref*{container-page-test-module-Ocamlary-emptySig}]} is the section and \hyperref[container-page-test-module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{container-page-test-module-Ocamlary-module-type-EmptySig}]} is the module signature.
+
+\label{container-page-test-module-Ocamlary-module-Buffer}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Buffer]{\ocamlinlinecode{Buffer}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Buffer-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[xref-unresolved]{\ocamlinlinecode{Stdlib}}.\allowbreak{}Buffer.\allowbreak{}t \ocamltag{arrow}{$\rightarrow$} unit}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}\ocamlinlinecode{Buffer}.t\end{ocamlindent}%
+\medbreak
+Some text before exception title.
+
+\subsubsection{Basic exception stuff\label{basic-exception-stuff}}%
+After exception title.
+
+\label{container-page-test-module-Ocamlary-exception-Kaboom}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kaboom} \ocamltag{keyword}{of} unit}\begin{ocamlindent}Unary exception constructor\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-exception-Kablam}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kablam} \ocamltag{keyword}{of} unit * unit}\begin{ocamlindent}Binary exception constructor\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-exception-Kapow}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kapow} \ocamltag{keyword}{of} unit * unit}\begin{ocamlindent}Unary exception constructor over binary tuple\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-exception-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{EmptySig}}\begin{ocamlindent}\hyperref[container-page-test-module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{container-page-test-module-Ocamlary-module-type-EmptySig}]} is a module and \hyperref[container-page-test-module-Ocamlary-exception-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{container-page-test-module-Ocamlary-exception-EmptySig}]} is this exception.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-exception-EmptySigAlias}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{EmptySigAlias}}\begin{ocamlindent}\hyperref[container-page-test-module-Ocamlary-exception-EmptySigAlias]{\ocamlinlinecode{\ocamlinlinecode{EmptySigAlias}}[p\pageref*{container-page-test-module-Ocamlary-exception-EmptySigAlias}]} is this exception.\end{ocamlindent}%
+\medbreak
+\subsubsection{Basic type and value stuff with advanced doc comments\label{basic-type-and-value-stuff-with-advanced-doc-comments}}%
+\label{container-page-test-module-Ocamlary-type-a+u+function}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) a\_\allowbreak{}function = \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}}\begin{ocamlindent}\hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{\ocamlinlinecode{a\_\allowbreak{}function}}[p\pageref*{container-page-test-module-Ocamlary-type-a+u+function}]} is this type and \hyperref[container-page-test-module-Ocamlary-val-a+u+function]{\ocamlinlinecode{\ocamlinlinecode{a\_\allowbreak{}function}}[p\pageref*{container-page-test-module-Ocamlary-val-a+u+function}]} is the value below.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-a+u+function}\ocamlcodefragment{\ocamltag{keyword}{val} a\_\allowbreak{}function : x:int \ocamltag{arrow}{$\rightarrow$} int}\begin{ocamlindent}This is \ocamlinlinecode{a\_\allowbreak{}function} with param and return type.\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{parameter x}]{the \ocamlinlinecode{x} coordinate}\end{description}%
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{returns}]{the \ocamlinlinecode{y} coordinate}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-fun+u+fun+u+fun}\ocamlcodefragment{\ocamltag{keyword}{val} fun\_\allowbreak{}fun\_\allowbreak{}fun : ((int,\allowbreak{} int) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}},\allowbreak{} (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\\
+\label{container-page-test-module-Ocamlary-val-fun+u+maybe}\ocamlcodefragment{\ocamltag{keyword}{val} fun\_\allowbreak{}maybe : ?yes:unit \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} int}\\
+\label{container-page-test-module-Ocamlary-val-not+u+found}\ocamlcodefragment{\ocamltag{keyword}{val} not\_\allowbreak{}found : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{raises Not\_\allowbreak{}found}]{That's all it does}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-ocaml+u+org}\ocamlcodefragment{\ocamltag{keyword}{val} ocaml\_\allowbreak{}org : string}\begin{ocamlindent}\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{see \href{http://ocaml.org/}{http://ocaml.org/}\footnote{\url{http://ocaml.org/}}}]{The OCaml Web site}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-some+u+file}\ocamlcodefragment{\ocamltag{keyword}{val} some\_\allowbreak{}file : string}\begin{ocamlindent}\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{see \ocamlinlinecode{some\_\allowbreak{}file}}]{The file called \ocamlinlinecode{some\_\allowbreak{}file}}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-some+u+doc}\ocamlcodefragment{\ocamltag{keyword}{val} some\_\allowbreak{}doc : string}\begin{ocamlindent}\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{see some\_\allowbreak{}doc}]{The document called \ocamlinlinecode{some\_\allowbreak{}doc}}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-since+u+mesozoic}\ocamlcodefragment{\ocamltag{keyword}{val} since\_\allowbreak{}mesozoic : unit}\begin{ocamlindent}This value was introduced in the Mesozoic era.\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{since}]{mesozoic}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-val-changing}\ocamlcodefragment{\ocamltag{keyword}{val} changing : unit}\begin{ocamlindent}This value has had changes in 1.0.0, 1.1.0, and 1.2.0.\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{before 1.\allowbreak{}0.\allowbreak{}0}]{before 1.0.0}\end{description}%
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{before 1.\allowbreak{}1.\allowbreak{}0}]{before 1.1.0}\end{description}%
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{version}]{1.2.0}\end{description}%
+\end{ocamlindent}%
+\medbreak
+\subsubsection{Some Operators\label{some-operators}}%
+\label{container-page-test-module-Ocamlary-val-(+t+-)}\ocamlcodefragment{\ocamltag{keyword}{val} (\textasciitilde{}-) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(!)}\ocamlcodefragment{\ocamltag{keyword}{val} (!) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(@)}\ocamlcodefragment{\ocamltag{keyword}{val} (@) : unit}\\
+\label{container-page-test-module-Ocamlary-val-($)}\ocamlcodefragment{\ocamltag{keyword}{val} (\$) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(%)}\ocamlcodefragment{\ocamltag{keyword}{val} (\%) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(&)}\ocamlcodefragment{\ocamltag{keyword}{val} (\&) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(*)}\ocamlcodefragment{\ocamltag{keyword}{val} (*) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(-)}\ocamlcodefragment{\ocamltag{keyword}{val} (-) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(+++)}\ocamlcodefragment{\ocamltag{keyword}{val} (+) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(-?)}\ocamlcodefragment{\ocamltag{keyword}{val} (-?) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(/)}\ocamlcodefragment{\ocamltag{keyword}{val} (/) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(:=)}\ocamlcodefragment{\ocamltag{keyword}{val} (:=) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(=)}\ocamlcodefragment{\ocamltag{keyword}{val} (=) : unit}\\
+\label{container-page-test-module-Ocamlary-val-(land)}\ocamlcodefragment{\ocamltag{keyword}{val} (land) : unit}\\
+\subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}%
+\label{container-page-test-module-Ocamlary-module-CollectionModule}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CollectionModule]{\ocamlinlinecode{CollectionModule}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CollectionModule-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-CollectionModule-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-CollectionModule-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CollectionModule-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-COLLECTION-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}module type of\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-Recollection}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Recollection]{\ocamlinlinecode{Recollection}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C]{\ocamlinlinecode{C}} : \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}}) : \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-type-collection]{\ocamlinlinecode{collection}} = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-element]{\ocamlinlinecode{C.\allowbreak{}element}} list \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION-type-element]{\ocamlinlinecode{element}} = \hyperref[container-page-test-module-Ocamlary-module-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{C.\allowbreak{}collection}}}\\
+\label{container-page-test-module-Ocamlary-module-type-MMM}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-MMM]{\ocamlinlinecode{MMM}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-MMM-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-MMM-module-C-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-RECOLLECTION}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-RECOLLECTION]{\ocamlinlinecode{RECOLLECTION}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-RECOLLECTION-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[container-page-test-module-Ocamlary-module-Recollection]{\ocamlinlinecode{Recollection(CollectionModule)}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-RecollectionModule}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule]{\ocamlinlinecode{RecollectionModule}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection = \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-type-element]{\ocamlinlinecode{CollectionModule.\allowbreak{}element}} list}\\
+\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element = \hyperref[container-page-test-module-Ocamlary-module-CollectionModule-type-collection]{\ocamlinlinecode{CollectionModule.\allowbreak{}collection}}}\\
+\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-RecollectionModule-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-A}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-A-module-Q-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-B}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-B-module-Q-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-C}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-A]{\ocamlinlinecode{A}}\label{container-page-test-module-Ocamlary-module-type-C-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.
+
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-a+u+function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-module-type-InnerModuleTypeA]{\ocamlinlinecode{InnerModuleTypeA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-C-module-Q-module-type-InnerModuleTypeA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-B]{\ocamlinlinecode{B}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-B-type-t]{\ocamlinlinecode{t}} := \hyperref[container-page-test-module-Ocamlary-module-type-C-type-t]{\ocamlinlinecode{t}} \ocamltag{keyword}{and} \ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-B-module-Q]{\ocamlinlinecode{Q}} := \hyperref[container-page-test-module-Ocamlary-module-type-C-module-Q]{\ocamlinlinecode{Q}}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This module type includes two signatures.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-FunctorTypeOf}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf]{\ocamlinlinecode{FunctorTypeOf}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-FunctorTypeOf-argument-1-Collection]{\ocamlinlinecode{Collection}} : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-module-CollectionModule]{\ocamlinlinecode{CollectionModule}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{FunctorTypeOf}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-IncludeModuleType}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-IncludeModuleType]{\ocamlinlinecode{IncludeModuleType}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{include EmptySigAlias}.\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-EmptySigAlias]{\ocamlinlinecode{EmptySigAlias}}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{IncludeModuleType}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-type-ToInclude}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-ToInclude]{\ocamlinlinecode{ToInclude}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-ToInclude-module-IncludedA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-ToInclude-module-IncludedA]{\ocamlinlinecode{IncludedA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-ToInclude-module-IncludedA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-ToInclude-module-type-IncludedB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-ToInclude-module-type-IncludedB]{\ocamlinlinecode{IncludedB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-ToInclude-module-type-IncludedB-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-ToInclude]{\ocamlinlinecode{ToInclude}}\label{container-page-test-module-Ocamlary-module-IncludedA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-IncludedA]{\ocamlinlinecode{IncludedA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-IncludedA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-IncludedB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-IncludedB]{\ocamlinlinecode{IncludedB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-IncludedB-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\subsubsection{Advanced Type Stuff\label{advanced-type-stuff}}%
+\label{container-page-test-module-Ocamlary-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{field1 : int;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-record.field1}& This comment is for \ocamlinlinecode{field1}.\\
+\ocamlinlinecode{field2 : int;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-record.field2}& This comment is for \ocamlinlinecode{field2}.\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\begin{ocamlindent}This comment is for \ocamlinlinecode{record}.This comment is also for \ocamlinlinecode{record}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-mutable+u+record}\ocamlcodefragment{\ocamltag{keyword}{type} mutable\_\allowbreak{}record = \{}\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{\ocamltag{keyword}{mutable} a : int;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-mutable+u+record.a}& \ocamlinlinecode{a} is first and mutable\\
+\ocamlinlinecode{b : unit;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-mutable+u+record.b}& \ocamlinlinecode{b} is second and immutable\\
+\ocamlinlinecode{\ocamltag{keyword}{mutable} c : int;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-mutable+u+record.c}& \ocamlinlinecode{c} is third and mutable\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\\
+\label{container-page-test-module-Ocamlary-type-universe+u+record}\ocamlcodefragment{\ocamltag{keyword}{type} universe\_\allowbreak{}record = \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{nihilate : a.\allowbreak{} \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-universe+u+record.nihilate}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\\
+\label{container-page-test-module-Ocamlary-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{TagA}}\label{container-page-test-module-Ocamlary-type-variant.TagA}& This comment is for \ocamlinlinecode{TagA}.\\
+\ocamlcodefragment{| \ocamltag{constructor}{ConstrB} \ocamltag{keyword}{of} int}\label{container-page-test-module-Ocamlary-type-variant.ConstrB}& This comment is for \ocamlinlinecode{ConstrB}.\\
+\ocamlcodefragment{| \ocamltag{constructor}{ConstrC} \ocamltag{keyword}{of} int * int}\label{container-page-test-module-Ocamlary-type-variant.ConstrC}& This comment is for binary \ocamlinlinecode{ConstrC}.\\
+\ocamlcodefragment{| \ocamltag{constructor}{ConstrD} \ocamltag{keyword}{of} int * int}\label{container-page-test-module-Ocamlary-type-variant.ConstrD}& This comment is for unary \ocamlinlinecode{ConstrD} of binary tuple.\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \ocamlinlinecode{variant}.This comment is also for \ocamlinlinecode{variant}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} poly\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`TagA}\label{container-page-test-module-Ocamlary-type-poly+u+variant.TagA}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`ConstrB \ocamltag{keyword}{of} int}\label{container-page-test-module-Ocamlary-type-poly+u+variant.ConstrB}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\begin{ocamlindent}This comment is for \ocamlinlinecode{poly\_\allowbreak{}variant}.Wow! It was a polymorphic variant!\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-full+u+gadt}\ocamlcodefragment{\ocamltag{keyword}{type} (\_\allowbreak{},\allowbreak{} \_\allowbreak{}) full\_\allowbreak{}gadt = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Tag} : (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt.Tag}\\
+\ocamlcodefragment{| \ocamltag{constructor}{First} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'a},\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt.First}\\
+\ocamlcodefragment{| \ocamltag{constructor}{Second} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (unit,\allowbreak{} \ocamltag{type-var}{'a}) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt.Second}\\
+\ocamlcodefragment{| \ocamltag{constructor}{Exist} : \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'b},\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt.Exist}\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \ocamlinlinecode{full\_\allowbreak{}gadt}.Wow! It was a GADT!\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-partial+u+gadt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a partial\_\allowbreak{}gadt = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{AscribeTag} : \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-partial+u+gadt.AscribeTag}\\
+\ocamlcodefragment{| \ocamltag{constructor}{OfTag} \ocamltag{keyword}{of} \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-partial+u+gadt.OfTag}\\
+\ocamlcodefragment{| \ocamltag{constructor}{ExistGadtTag} : (\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}) \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{container-page-test-module-Ocamlary-type-partial+u+gadt.ExistGadtTag}\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \ocamlinlinecode{partial\_\allowbreak{}gadt}.Wow! It was a mixed GADT!\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = \hyperref[container-page-test-module-Ocamlary-type-variant]{\ocamlinlinecode{variant}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{alias}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-tuple}\ocamlcodefragment{\ocamltag{keyword}{type} tuple = (\hyperref[container-page-test-module-Ocamlary-type-alias]{\ocamlinlinecode{alias}} * \hyperref[container-page-test-module-Ocamlary-type-alias]{\ocamlinlinecode{alias}}) * \hyperref[container-page-test-module-Ocamlary-type-alias]{\ocamlinlinecode{alias}} * (\hyperref[container-page-test-module-Ocamlary-type-alias]{\ocamlinlinecode{alias}} * \hyperref[container-page-test-module-Ocamlary-type-alias]{\ocamlinlinecode{alias}})}\begin{ocamlindent}This comment is for \ocamlinlinecode{tuple}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-variant+u+alias}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}alias = \hyperref[container-page-test-module-Ocamlary-type-variant]{\ocamlinlinecode{variant}} = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{TagA}}\label{container-page-test-module-Ocamlary-type-variant+u+alias.TagA}\\
+\ocamlcodefragment{| \ocamltag{constructor}{ConstrB} \ocamltag{keyword}{of} int}\label{container-page-test-module-Ocamlary-type-variant+u+alias.ConstrB}\\
+\ocamlcodefragment{| \ocamltag{constructor}{ConstrC} \ocamltag{keyword}{of} int * int}\label{container-page-test-module-Ocamlary-type-variant+u+alias.ConstrC}\\
+\ocamlcodefragment{| \ocamltag{constructor}{ConstrD} \ocamltag{keyword}{of} int * int}\label{container-page-test-module-Ocamlary-type-variant+u+alias.ConstrD}\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \ocamlinlinecode{variant\_\allowbreak{}alias}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-record+u+alias}\ocamlcodefragment{\ocamltag{keyword}{type} record\_\allowbreak{}alias = \hyperref[container-page-test-module-Ocamlary-type-record]{\ocamlinlinecode{record}} = \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field1 : int;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-record+u+alias.field1}\\
+\ocamlinlinecode{field2 : int;\allowbreak{}}\label{container-page-test-module-Ocamlary-type-record+u+alias.field2}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\begin{ocamlindent}This comment is for \ocamlinlinecode{record\_\allowbreak{}alias}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-poly+u+variant+u+union}\ocamlcodefragment{\ocamltag{keyword}{type} poly\_\allowbreak{}variant\_\allowbreak{}union = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[container-page-test-module-Ocamlary-type-poly+u+variant]{\ocamlinlinecode{poly\_\allowbreak{}variant}}}\label{container-page-test-module-Ocamlary-type-poly+u+variant+u+union.poly+u+variant}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`TagC}\label{container-page-test-module-Ocamlary-type-poly+u+variant+u+union.TagC}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\begin{ocamlindent}This comment is for \ocamlinlinecode{poly\_\allowbreak{}variant\_\allowbreak{}union}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-poly+u+poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`TagA \ocamltag{keyword}{of} \ocamltag{type-var}{'a}}\label{container-page-test-module-Ocamlary-type-poly+u+poly+u+variant.TagA}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Ocamlary-type-bin+u+poly+u+poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) bin\_\allowbreak{}poly\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`TagA \ocamltag{keyword}{of} \ocamltag{type-var}{'a}}\label{container-page-test-module-Ocamlary-type-bin+u+poly+u+poly+u+variant.TagA}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`ConstrB \ocamltag{keyword}{of} \ocamltag{type-var}{'b}}\label{container-page-test-module-Ocamlary-type-bin+u+poly+u+poly+u+variant.ConstrB}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Ocamlary-type-open+u+poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant = [> `TagA ] \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-type-open+u+poly+u+variant2}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant2 = [> `ConstrB of int ] \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-type-open+u+poly+u+variant+u+alias}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant\_\allowbreak{}alias = \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-open+u+poly+u+variant]{\ocamlinlinecode{open\_\allowbreak{}poly\_\allowbreak{}variant}} \hyperref[container-page-test-module-Ocamlary-type-open+u+poly+u+variant2]{\ocamlinlinecode{open\_\allowbreak{}poly\_\allowbreak{}variant2}}}\\
+\label{container-page-test-module-Ocamlary-type-poly+u+fun}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}fun = [> `ConstrB of int ] \ocamltag{keyword}{as} 'a \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a}}\\
+\label{container-page-test-module-Ocamlary-type-poly+u+fun+u+constraint}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}fun\_\allowbreak{}constraint = \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `TagA ]}\\
+\label{container-page-test-module-Ocamlary-type-closed+u+poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a closed\_\allowbreak{}poly\_\allowbreak{}variant = [< `One | `Two ] \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-type-clopen+u+poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a clopen\_\allowbreak{}poly\_\allowbreak{}variant = [< `One | `Two of int | `Three Two Three ] \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-type-nested+u+poly+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test-module-Ocamlary-type-nested+u+poly+u+variant.A}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} [ `B1 | `B2 ]}\label{container-page-test-module-Ocamlary-type-nested+u+poly+u+variant.B}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`C}\label{container-page-test-module-Ocamlary-type-nested+u+poly+u+variant.C}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`D \ocamltag{keyword}{of} [ `D1 of [ `D1a ] ]}\label{container-page-test-module-Ocamlary-type-nested+u+poly+u+variant.D}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Ocamlary-type-full+u+gadt+u+alias}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) full\_\allowbreak{}gadt\_\allowbreak{}alias = (\ocamltag{type-var}{'a},\allowbreak{} \ocamltag{type-var}{'b}) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}} = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Tag} : (unit,\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt+u+alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt+u+alias.Tag}\\
+\ocamlcodefragment{| \ocamltag{constructor}{First} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'a},\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt+u+alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt+u+alias.First}\\
+\ocamlcodefragment{| \ocamltag{constructor}{Second} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (unit,\allowbreak{} \ocamltag{type-var}{'a}) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt+u+alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt+u+alias.Second}\\
+\ocamlcodefragment{| \ocamltag{constructor}{Exist} : \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'b},\allowbreak{} unit) \hyperref[container-page-test-module-Ocamlary-type-full+u+gadt+u+alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-full+u+gadt+u+alias.Exist}\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias}\ocamlcodefragment{\ocamltag{keyword}{type} 'a partial\_\allowbreak{}gadt\_\allowbreak{}alias = \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}} = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{AscribeTag} : \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias.AscribeTag}\\
+\ocamlcodefragment{| \ocamltag{constructor}{OfTag} \ocamltag{keyword}{of} \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias.OfTag}\\
+\ocamlcodefragment{| \ocamltag{constructor}{ExistGadtTag} : (\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}) \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{container-page-test-module-Ocamlary-type-partial+u+gadt+u+alias.ExistGadtTag}\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-exception-Exn+u+arrow}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Exn\_\allowbreak{}arrow} : unit \ocamltag{arrow}{$\rightarrow$} exn}\begin{ocamlindent}This comment is for \hyperref[container-page-test-module-Ocamlary-exception-Exn+u+arrow]{\ocamlinlinecode{\ocamlinlinecode{Exn\_\allowbreak{}arrow}}[p\pageref*{container-page-test-module-Ocamlary-exception-Exn+u+arrow}]}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-mutual+u+constr+u+a}\ocamlcodefragment{\ocamltag{keyword}{type} mutual\_\allowbreak{}constr\_\allowbreak{}a = }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test-module-Ocamlary-type-mutual+u+constr+u+a.A}& \\
+\ocamlcodefragment{| \ocamltag{constructor}{B\_\allowbreak{}ish} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+b]{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}}\label{container-page-test-module-Ocamlary-type-mutual+u+constr+u+a.B+u+ish}& This comment is between \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{container-page-test-module-Ocamlary-type-mutual+u+constr+u+a}]} and \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{container-page-test-module-Ocamlary-type-mutual+u+constr+u+b}]}.\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{container-page-test-module-Ocamlary-type-mutual+u+constr+u+a}]} then \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{container-page-test-module-Ocamlary-type-mutual+u+constr+u+b}]}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-mutual+u+constr+u+b}\ocamlcodefragment{\ocamltag{keyword}{and} mutual\_\allowbreak{}constr\_\allowbreak{}b = }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{container-page-test-module-Ocamlary-type-mutual+u+constr+u+b.B}& \\
+\ocamlcodefragment{| \ocamltag{constructor}{A\_\allowbreak{}ish} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+a]{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}}\label{container-page-test-module-Ocamlary-type-mutual+u+constr+u+b.A+u+ish}& This comment must be here for the next to associate correctly.\\
+\end{ocamltabular}%
+\\
+\begin{ocamlindent}This comment is for \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{container-page-test-module-Ocamlary-type-mutual+u+constr+u+b}]} then \hyperref[container-page-test-module-Ocamlary-type-mutual+u+constr+u+a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{container-page-test-module-Ocamlary-type-mutual+u+constr+u+a}]}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-rec+u+obj}\ocamlcodefragment{\ocamltag{keyword}{type} rec\_\allowbreak{}obj = < f : int;\allowbreak{} g : unit \ocamltag{arrow}{$\rightarrow$} unit;\allowbreak{} h : \hyperref[container-page-test-module-Ocamlary-type-rec+u+obj]{\ocamlinlinecode{rec\_\allowbreak{}obj}};\allowbreak{} >}\\
+\label{container-page-test-module-Ocamlary-type-open+u+obj}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}obj = < f : int;\allowbreak{} g : unit \ocamltag{arrow}{$\rightarrow$} unit;\allowbreak{} .\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-type-oof}\ocamlcodefragment{\ocamltag{keyword}{type} 'a oof = < a : unit;\allowbreak{} .\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a}}\\
+\label{container-page-test-module-Ocamlary-type-any+u+obj}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}obj = < .\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-type-empty+u+obj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}obj = < >}\\
+\label{container-page-test-module-Ocamlary-type-one+u+meth}\ocamlcodefragment{\ocamltag{keyword}{type} one\_\allowbreak{}meth = < meth : unit;\allowbreak{} >}\\
+\label{container-page-test-module-Ocamlary-type-ext}\ocamlcodefragment{\ocamltag{keyword}{type} ext = .\allowbreak{}.\allowbreak{}}\begin{ocamlindent}A mystery wrapped in an ellipsis\end{ocamlindent}%
+\medbreak
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtA}}\label{container-page-test-module-Ocamlary-extension-ExtA}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtB}}\label{container-page-test-module-Ocamlary-extension-ExtB}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtC} \ocamltag{keyword}{of} unit}\label{container-page-test-module-Ocamlary-extension-ExtC}\\
+\ocamlcodefragment{| \ocamltag{extension}{ExtD} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-type-ext]{\ocamlinlinecode{ext}}}\label{container-page-test-module-Ocamlary-extension-ExtD}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtE}}\label{container-page-test-module-Ocamlary-extension-ExtE}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtF}}\label{container-page-test-module-Ocamlary-extension-ExtF}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Ocamlary-type-poly+u+ext}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}ext = .\allowbreak{}.\allowbreak{}}\begin{ocamlindent}'a poly\_ext\end{ocamlindent}%
+\medbreak
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-poly+u+ext]{\ocamlinlinecode{poly\_\allowbreak{}ext}} += }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Foo} \ocamltag{keyword}{of} \ocamltag{type-var}{'b}}\label{container-page-test-module-Ocamlary-extension-Foo}& \\
+\ocamlcodefragment{| \ocamltag{extension}{Bar} \ocamltag{keyword}{of} \ocamltag{type-var}{'b} * \ocamltag{type-var}{'b}}\label{container-page-test-module-Ocamlary-extension-Bar}& 'b poly\_ext\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-poly+u+ext]{\ocamlinlinecode{poly\_\allowbreak{}ext}} += }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Quux} \ocamltag{keyword}{of} \ocamltag{type-var}{'c}}\label{container-page-test-module-Ocamlary-extension-Quux}& 'c poly\_ext\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Ocamlary-module-ExtMod}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-ExtMod]{\ocamlinlinecode{ExtMod}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-ExtMod-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = .\allowbreak{}.\allowbreak{}}\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-ExtMod-type-t]{\ocamlinlinecode{t}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Leisureforce}}\label{container-page-test-module-Ocamlary-module-ExtMod-extension-Leisureforce}\\
+\end{ocamltabular}%
+\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-ExtMod-type-t]{\ocamlinlinecode{ExtMod.\allowbreak{}t}} += }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ZzzTop0}}\label{container-page-test-module-Ocamlary-extension-ZzzTop0}& It's got the rock\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-ExtMod-type-t]{\ocamlinlinecode{ExtMod.\allowbreak{}t}} += }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ZzzTop} \ocamltag{keyword}{of} unit}\label{container-page-test-module-Ocamlary-extension-ZzzTop}& and it packs a unit.\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Ocamlary-val-launch+u+missiles}\ocamlcodefragment{\ocamltag{keyword}{val} launch\_\allowbreak{}missiles : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Rotate keys on my mark...\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-type-my+u+mod}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}mod = (\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}})}\begin{ocamlindent}A brown paper package tied up with string\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-class-empty+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Ocamlary-class-empty+u+class]{\ocamlinlinecode{empty\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-class-one+u+method+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Ocamlary-class-one+u+method+u+class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-class-two+u+method+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Ocamlary-class-two+u+method+u+class]{\ocamlinlinecode{two\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-class-param+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[container-page-test-module-Ocamlary-class-param+u+class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-type-my+u+unit+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}unit\_\allowbreak{}object = unit \hyperref[container-page-test-module-Ocamlary-class-param+u+class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\\
+\label{container-page-test-module-Ocamlary-type-my+u+unit+u+class}\ocamlcodefragment{\ocamltag{keyword}{type} 'a my\_\allowbreak{}unit\_\allowbreak{}class = unit \hyperref[xref-unresolved]{\ocamlinlinecode{param\_\allowbreak{}class}} \ocamltag{keyword}{as} 'a}\\
+\label{container-page-test-module-Ocamlary-module-Dep1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep1]{\ocamlinlinecode{Dep1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep1-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep1-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep1-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Ocamlary-module-Dep1-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep1-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep1-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep1-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep1-module-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep1-module-X-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-Dep1-module-type-S]{\ocamlinlinecode{S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep2]{\ocamlinlinecode{Dep2}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-Dep2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-type-dep1}\ocamlcodefragment{\ocamltag{keyword}{type} dep1 = \hyperref[container-page-test-module-Ocamlary-module-Dep1-module-type-S-class-c]{\ocamlinlinecode{Dep2(Dep1).\allowbreak{}B.\allowbreak{}c}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep3]{\ocamlinlinecode{Dep3}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep3-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep4]{\ocamlinlinecode{Dep4}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep4-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep4-module-type-T-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep4-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep4-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-type-S-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep4-module-type-S-module-X-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep4-module-type-S-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-type-S-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep4-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-type-T]{\ocamlinlinecode{T}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep5]{\ocamlinlinecode{Dep5}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-Dep5-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-type-dep2}\ocamlcodefragment{\ocamltag{keyword}{type} dep2 = \hyperref[container-page-test-module-Ocamlary-module-Dep4-module-type-T-type-b]{\ocamlinlinecode{Dep5(Dep4).\allowbreak{}Z.\allowbreak{}X.\allowbreak{}b}}}\\
+\label{container-page-test-module-Ocamlary-type-dep3}\ocamlcodefragment{\ocamltag{keyword}{type} dep3 = \hyperref[container-page-test-module-Ocamlary-module-Dep3-type-a]{\ocamlinlinecode{Dep5(Dep4).\allowbreak{}Z.\allowbreak{}Y.\allowbreak{}a}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep6}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep6]{\ocamlinlinecode{Dep6}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep6-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep6-module-type-S-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep6-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-type-R]{\ocamlinlinecode{R}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-type-R-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-Y-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep6-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-type-T]{\ocamlinlinecode{T}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep7}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep7]{\ocamlinlinecode{Dep7}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-Dep7-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-type-dep4}\ocamlcodefragment{\ocamltag{keyword}{type} dep4 = \hyperref[container-page-test-module-Ocamlary-module-Dep6-module-type-T-module-Y-type-d]{\ocamlinlinecode{Dep7(Dep6).\allowbreak{}M.\allowbreak{}Y.\allowbreak{}d}}}\\
+\label{container-page-test-module-Ocamlary-module-Dep8}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep8]{\ocamlinlinecode{Dep8}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep8-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep8-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep8-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep9}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep9]{\ocamlinlinecode{Dep9}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-Dep9-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-Dep10}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-Dep10]{\ocamlinlinecode{Dep10}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-Dep10-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep11}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep11]{\ocamlinlinecode{Dep11}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep11-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-Dep11-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep11-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Ocamlary-module-Dep11-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Dep11-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep12}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep12]{\ocamlinlinecode{Dep12}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-Dep12-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Dep13}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Dep13]{\ocamlinlinecode{Dep13}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-Dep11-module-type-S]{\ocamlinlinecode{Dep12(Dep11).\allowbreak{}T}}}\\
+\label{container-page-test-module-Ocamlary-type-dep5}\ocamlcodefragment{\ocamltag{keyword}{type} dep5 = \hyperref[container-page-test-module-Ocamlary-module-Dep13-class-c]{\ocamlinlinecode{Dep13.\allowbreak{}c}}}\\
+\label{container-page-test-module-Ocamlary-module-type-With1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-With1]{\ocamlinlinecode{With1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With1-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-With1-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With1-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-With1-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[container-page-test-module-Ocamlary-module-type-With1-module-M-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With2-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-With2-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With2-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With3]{\ocamlinlinecode{With3}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-type-With1]{\ocamlinlinecode{With1}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-With1-module-M]{\ocamlinlinecode{M}} = \hyperref[container-page-test-module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\\
+\label{container-page-test-module-Ocamlary-type-with1}\ocamlcodefragment{\ocamltag{keyword}{type} with1 = \hyperref[container-page-test-module-Ocamlary-module-With3-module-N-type-t]{\ocamlinlinecode{With3.\allowbreak{}N.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-With4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With4]{\ocamlinlinecode{With4}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-type-With1]{\ocamlinlinecode{With1}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-With1-module-M]{\ocamlinlinecode{M}} := \hyperref[container-page-test-module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\\
+\label{container-page-test-module-Ocamlary-type-with2}\ocamlcodefragment{\ocamltag{keyword}{type} with2 = \hyperref[container-page-test-module-Ocamlary-module-With4-module-N-type-t]{\ocamlinlinecode{With4.\allowbreak{}N.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-With5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With5]{\ocamlinlinecode{With5}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With5-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-With5-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With5-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With5-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With5-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Ocamlary-module-With5-module-type-S]{\ocamlinlinecode{S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With6}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With6]{\ocamlinlinecode{With6}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With6-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-With6-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With6-module-type-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With6-module-type-T-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With6-module-type-T-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\
+\label{container-page-test-module-Ocamlary-module-With6-module-type-T-module-M-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[container-page-test-module-Ocamlary-module-With6-module-type-T-module-M-module-type-S]{\ocamlinlinecode{S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With7}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With7]{\ocamlinlinecode{With7}}}\ocamlcodefragment{ (\hyperref[container-page-test-module-Ocamlary-module-With7-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-With8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-With8]{\ocamlinlinecode{With8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With8-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-With8-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With8-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-With8-module-M-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With8-module-M-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-With8-module-M-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-With8-module-M-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With8-module-M-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test-module-Ocamlary-module-With5-module-N-type-t]{\ocamlinlinecode{With5.\allowbreak{}N.\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With9}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With9]{\ocamlinlinecode{With9}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With9-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-With9-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With9-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With10}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With10]{\ocamlinlinecode{With10}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With10-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-With10-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With10-module-type-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-With10-module-type-T-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-With10-module-type-T-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-With10-module-type-T-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[container-page-test-module-Ocamlary-module-With10-module-type-T-module-M-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}\hyperref[container-page-test-module-Ocamlary-module-With10-module-type-T]{\ocamlinlinecode{\ocamlinlinecode{With10.\allowbreak{}T}}[p\pageref*{container-page-test-module-Ocamlary-module-With10-module-type-T}]} is a submodule type.\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-With11}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-With11]{\ocamlinlinecode{With11}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With11-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[container-page-test-module-Ocamlary-module-With9]{\ocamlinlinecode{With9}}}\\
+\label{container-page-test-module-Ocamlary-module-type-With11-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-type-With11-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-With11-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-type-NestedInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-NestedInclude1]{\ocamlinlinecode{NestedInclude1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2-type-nested+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-NestedInclude1]{\ocamlinlinecode{NestedInclude1}}\label{container-page-test-module-Ocamlary-module-type-NestedInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-NestedInclude2-type-nested+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-NestedInclude2-type-nested+u+include]{\ocamlinlinecode{nested\_\allowbreak{}include}} = int\label{container-page-test-module-Ocamlary-type-nested+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include = int}\\
+\label{container-page-test-module-Ocamlary-module-DoubleInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-DoubleInclude1]{\ocamlinlinecode{DoubleInclude1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-DoubleInclude1-module-DoubleInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-DoubleInclude1-module-DoubleInclude2]{\ocamlinlinecode{DoubleInclude2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-DoubleInclude1-module-DoubleInclude2-type-double+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-DoubleInclude3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-DoubleInclude3]{\ocamlinlinecode{DoubleInclude3}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-module-DoubleInclude1]{\ocamlinlinecode{DoubleInclude1}}\label{container-page-test-module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2]{\ocamlinlinecode{DoubleInclude2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2-type-double+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2]{\ocamlinlinecode{DoubleInclude3.\allowbreak{}DoubleInclude2}}\label{container-page-test-module-Ocamlary-type-double+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\
+\label{container-page-test-module-Ocamlary-module-IncludeInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-IncludeInclude1]{\ocamlinlinecode{IncludeInclude1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-IncludeInclude1-module-type-IncludeInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-IncludeInclude1-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-IncludeInclude1-module-type-IncludeInclude2-type-include+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-module-IncludeInclude1]{\ocamlinlinecode{IncludeInclude1}}\label{container-page-test-module-Ocamlary-module-type-IncludeInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-IncludeInclude2-type-include+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\ocamltag{keyword}{include} \hyperref[container-page-test-module-Ocamlary-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}\label{container-page-test-module-Ocamlary-type-include+u+include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\
+\subsection{Trying the \{!modules: ...\} command.\label{indexmodules}}%
+With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references.
+
+With odoc, everything should be resolved (and linked) but only toplevel units will be documented.
+
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{\hyperref[container-page-test-module-Ocamlary-module-Dep1-module-X]{\ocamlinlinecode{\ocamlinlinecode{Dep1.\allowbreak{}X}}[p\pageref*{container-page-test-module-Ocamlary-module-Dep1-module-X}]}}]{}%
+\item[{\ocamlinlinecode{DocOckTypes}}]{}%
+\item[{\hyperref[container-page-test-module-Ocamlary-module-IncludeInclude1]{\ocamlinlinecode{\ocamlinlinecode{Ocamlary.\allowbreak{}IncludeInclude1}}[p\pageref*{container-page-test-module-Ocamlary-module-IncludeInclude1}]}}]{}%
+\item[{\hyperref[container-page-test-module-Ocamlary]{\ocamlinlinecode{\ocamlinlinecode{Ocamlary}}[p\pageref*{container-page-test-module-Ocamlary}]}}]{This is an \emph{interface} with \bold{all} of the \emph{module system} features. This documentation demonstrates:}\end{description}%
+\subsubsection{Weirder usages involving module types\label{weirder-usages-involving-module-types}}%
+\begin{description}\kern-\topsep
+\makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
+\item[{\ocamlinlinecode{IncludeInclude1}.IncludeInclude2}]{}%
+\item[{\ocamlinlinecode{Dep4}.T}]{}%
+\item[{\hyperref[container-page-test-module-Ocamlary-module-type-A-module-Q]{\ocamlinlinecode{\ocamlinlinecode{A.\allowbreak{}Q}}[p\pageref*{container-page-test-module-Ocamlary-module-type-A-module-Q}]}}]{}\end{description}%
+\subsection{Playing with @canonical paths\label{playing-with-@canonical-paths}}%
+\label{container-page-test-module-Ocamlary-module-CanonicalTest}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest]{\ocamlinlinecode{CanonicalTest}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+List}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+List]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}List}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+List-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} 'a t}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+List-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \ocamltag{type-var}{'a} \hyperref[xref-unresolved]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[xref-unresolved]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+-module-List}\ocamlcodefragment{\ocamltag{keyword}{module} List = \hyperref[xref-unresolved]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}List}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base]{\ocamlinlinecode{Base}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{List}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}Tests}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}}.\allowbreak{}List}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L = \hyperref[xref-unresolved]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}}.\allowbreak{}List}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : \hyperref[xref-unresolved]{\ocamlinlinecode{int}} \hyperref[xref-unresolved]{\ocamlinlinecode{L}}.\allowbreak{}t \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{float}} \hyperref[xref-unresolved]{\ocamlinlinecode{L}}.\allowbreak{}t}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : \ocamltag{type-var}{'a} \hyperref[xref-unresolved]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}}.\allowbreak{}List.\allowbreak{}t \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[xref-unresolved]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}}.\allowbreak{}List.\allowbreak{}t}\begin{ocamlindent}This is just \ocamlinlinecode{List}.id, or rather \ocamlinlinecode{L}.id\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-val-baz}\ocamlcodefragment{\ocamltag{keyword}{val} baz : \ocamltag{type-var}{'a} \hyperref[xref-unresolved]{\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}}.\allowbreak{}List.\allowbreak{}t \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{unit}}}\begin{ocamlindent}Just seeing if \ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}}.List.t (\ocamlinlinecode{Base\_\allowbreak{}\_\allowbreak{}.\allowbreak{}List.\allowbreak{}t}) gets rewriten to \ocamlinlinecode{Base}.List.t (\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t})\end{ocamlindent}%
+\medbreak
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-CanonicalTest-module-List+u+modif}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-List+u+modif]{\ocamlinlinecode{List\_\allowbreak{}modif}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} 'c \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{t}} = \ocamltag{type-var}{'c} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-val-test}\ocamlcodefragment{\ocamltag{keyword}{val} test : \ocamltag{type-var}{'a} \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Some ref to \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-module-C-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}\_\allowbreak{}Tests.\allowbreak{}C.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+Tests-module-C-type-t}]} and \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}\_\allowbreak{}Tests.\allowbreak{}L.\allowbreak{}id}}[p\pageref*{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id}]}. But also to \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+-module-List]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}\_\allowbreak{}.\allowbreak{}List}}[p\pageref*{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+-module-List}]} and \hyperref[container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+-module-List-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}\_\allowbreak{}.\allowbreak{}List.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-CanonicalTest-module-Base+u++u+-module-List-type-t}]}\end{ocamlindent}%
+\medbreak
+\subsection{Aliases again\label{aliases}}%
+\label{container-page-test-module-Ocamlary-module-Aliases}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases]{\ocamlinlinecode{Aliases}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+A]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+A-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[xref-unresolved]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+B]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+B-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[xref-unresolved]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+C]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+C-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+C-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[xref-unresolved]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+D}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+D]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}D}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+D-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+D-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[xref-unresolved]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+E]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+E-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+E-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[xref-unresolved]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[xref-unresolved]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[xref-unresolved]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}A}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[xref-unresolved]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}B}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[xref-unresolved]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}C}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[xref-unresolved]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}D}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo+u++u+-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} E = \hyperref[xref-unresolved]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}E}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-D]{\ocamlinlinecode{D}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-A'}\ocamlcodefragment{\ocamltag{keyword}{module} A' = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-tata}\ocamlcodefragment{\ocamltag{keyword}{type} tata = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{Foo.\allowbreak{}A.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-tbtb}\ocamlcodefragment{\ocamltag{keyword}{type} tbtb = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B-type-t]{\ocamlinlinecode{Foo.\allowbreak{}B.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-tete}\ocamlcodefragment{\ocamltag{keyword}{type} tete}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-tata'}\ocamlcodefragment{\ocamltag{keyword}{type} tata' = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{A'.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-tete2}\ocamlcodefragment{\ocamltag{keyword}{type} tete2 = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-E-type-t]{\ocamlinlinecode{Foo.\allowbreak{}E.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Std}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Std]{\ocamlinlinecode{Std}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-Std-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Std-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Std-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-C]{\ocamlinlinecode{Foo.\allowbreak{}C}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Std-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-D]{\ocamlinlinecode{Foo.\allowbreak{}D}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-Std-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} E = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-E]{\ocamlinlinecode{Foo.\allowbreak{}E}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-stde}\ocamlcodefragment{\ocamltag{keyword}{type} stde = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-E-type-t]{\ocamlinlinecode{Std.\allowbreak{}E.\allowbreak{}t}}}\\
+\subsubsection{include of Foo\label{incl}}%
+Just for giggle, let's see what happens when we include \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{\ocamlinlinecode{Foo}}[p\pageref*{container-page-test-module-Ocamlary-module-Aliases-module-Foo}]}.
+
+\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{Foo}}\label{container-page-test-module-Ocamlary-module-Aliases-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-C]{\ocamlinlinecode{Foo.\allowbreak{}C}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-D]{\ocamlinlinecode{Foo.\allowbreak{}D}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-testa}\ocamlcodefragment{\ocamltag{keyword}{type} testa = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{A.\allowbreak{}t}}}\\
+And also, let's refer to \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{\ocamlinlinecode{A.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-A-type-t}]} and \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B-val-id]{\ocamlinlinecode{\ocamlinlinecode{Foo.\allowbreak{}B.\allowbreak{}id}}[p\pageref*{container-page-test-module-Ocamlary-module-Aliases-module-Foo-module-B-val-id}]}
+
+\label{container-page-test-module-Ocamlary-module-Aliases-module-P1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1]{\ocamlinlinecode{P1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y-type-t]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y-type-t]{\ocamlinlinecode{t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-P2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P2]{\ocamlinlinecode{P2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Aliases-module-P2-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} Z = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y]{\ocamlinlinecode{Z}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-X1}\ocamlcodefragment{\ocamltag{keyword}{module} X1 = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y]{\ocamlinlinecode{P2.\allowbreak{}Z}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-module-X2}\ocamlcodefragment{\ocamltag{keyword}{module} X2 = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y]{\ocamlinlinecode{P2.\allowbreak{}Z}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-p1}\ocamlcodefragment{\ocamltag{keyword}{type} p1 = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y-type-t]{\ocamlinlinecode{X1.\allowbreak{}t}}}\\
+\label{container-page-test-module-Ocamlary-module-Aliases-type-p2}\ocamlcodefragment{\ocamltag{keyword}{type} p2 = \hyperref[container-page-test-module-Ocamlary-module-Aliases-module-P1-module-Y-type-t]{\ocamlinlinecode{X2.\allowbreak{}t}}}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Let's imitate jst's layout.\end{ocamlindent}%
+\medbreak
+\subsection{Section title splicing\label{section-title-splicing}}%
+I can refer to
+
+\begin{itemize}\item{\ocamlinlinecode{\{!section:indexmodules\}} : \hyperref[container-page-test-module-Ocamlary-indexmodules]{\ocamlinlinecode{Trying the \{!modules: ...\} command.}[p\pageref*{container-page-test-module-Ocamlary-indexmodules}]}}%
+\item{\ocamlinlinecode{\{!aliases\}} : \hyperref[container-page-test-module-Ocamlary-aliases]{\ocamlinlinecode{Aliases again}[p\pageref*{container-page-test-module-Ocamlary-aliases}]}}\end{itemize}%
+But also to things in submodules:
+
+\begin{itemize}\item{\ocamlinlinecode{\{!section:SuperSig.\allowbreak{}SubSigA.\allowbreak{}subSig\}} : \ocamlinlinecode{SuperSig}.SubSigA.subSig}%
+\item{\ocamlinlinecode{\{!Aliases.\allowbreak{}incl\}} : \hyperref[container-page-test-module-Ocamlary-module-Aliases-incl]{\ocamlinlinecode{\ocamlinlinecode{Aliases:incl}}[p\pageref*{container-page-test-module-Ocamlary-module-Aliases-incl}]}}\end{itemize}%
+And just to make sure we do not mess up:
+
+\begin{itemize}\item{\ocamlinlinecode{\{\{!section:indexmodules\}A\}} : \hyperref[container-page-test-module-Ocamlary-indexmodules]{\ocamlinlinecode{A}[p\pageref*{container-page-test-module-Ocamlary-indexmodules}]}}%
+\item{\ocamlinlinecode{\{\{!aliases\}B\}} : \hyperref[container-page-test-module-Ocamlary-aliases]{\ocamlinlinecode{B}[p\pageref*{container-page-test-module-Ocamlary-aliases}]}}%
+\item{\ocamlinlinecode{\{\{!section:SuperSig.\allowbreak{}SubSigA.\allowbreak{}subSig\}C\}} : \hyperref[xref-unresolved]{\ocamlinlinecode{C}[p\pageref*{xref-unresolved}]}}%
+\item{\ocamlinlinecode{\{\{!Aliases.\allowbreak{}incl\}D\}} : \hyperref[container-page-test-module-Ocamlary-module-Aliases-incl]{\ocamlinlinecode{D}[p\pageref*{container-page-test-module-Ocamlary-module-Aliases-incl}]}}\end{itemize}%
+\subsection{New reference syntax\label{new-reference-syntax}}%
+\label{container-page-test-module-Ocamlary-module-type-M}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+Here goes:
+
+\begin{itemize}\item{\ocamlinlinecode{\{!module-M.\allowbreak{}t\}} : \hyperref[container-page-test-module-Ocamlary-module-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-M-type-t}]}}%
+\item{\ocamlinlinecode{\{!module-type-M.\allowbreak{}t\}} : \hyperref[container-page-test-module-Ocamlary-module-type-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-type-M-type-t}]}}\end{itemize}%
+\label{container-page-test-module-Ocamlary-module-Only+u+a+u+module}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Ocamlary-module-Only+u+a+u+module]{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-Only+u+a+u+module-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+Some here should fail:
+
+\begin{itemize}\item{\ocamlinlinecode{\{!Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[container-page-test-module-Ocamlary-module-Only+u+a+u+module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-Only+u+a+u+module-type-t}]}}%
+\item{\ocamlinlinecode{\{!module-Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[container-page-test-module-Ocamlary-module-Only+u+a+u+module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{container-page-test-module-Ocamlary-module-Only+u+a+u+module-type-t}]}}%
+\item{\ocamlinlinecode{\{!module-type-Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module}.t : \hyperref[xref-unresolved]{\ocamlinlinecode{test}[p\pageref*{xref-unresolved}]}}\end{itemize}%
+\label{container-page-test-module-Ocamlary-module-type-TypeExt}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-TypeExt]{\ocamlinlinecode{TypeExt}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Ocamlary-module-type-TypeExt-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = .\allowbreak{}.\allowbreak{}}\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-TypeExt-type-t]{\ocamlinlinecode{t}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{container-page-test-module-Ocamlary-module-type-TypeExt-extension-C}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Ocamlary-module-type-TypeExt-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[container-page-test-module-Ocamlary-module-type-TypeExt-type-t]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} unit}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Ocamlary-type-new+u+t}\ocamlcodefragment{\ocamltag{keyword}{type} new\_\allowbreak{}t = .\allowbreak{}.\allowbreak{}}\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-new+u+t]{\ocamlinlinecode{new\_\allowbreak{}t}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{container-page-test-module-Ocamlary-extension-C}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Ocamlary-module-type-TypeExtPruned}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-module-type-TypeExtPruned]{\ocamlinlinecode{TypeExtPruned}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Ocamlary-type-new+u+t]{\ocamlinlinecode{new\_\allowbreak{}t}} += }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{container-page-test-module-Ocamlary-module-type-TypeExtPruned-extension-C}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Ocamlary-module-type-TypeExtPruned-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[container-page-test-module-Ocamlary-type-new+u+t]{\ocamlinlinecode{new\_\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+
+\input{test/Ocamlary.ModuleWithSignature.tex}
+\input{test/Ocamlary.ModuleWithSignatureAlias.tex}
+\input{test/Ocamlary.Recollection.tex}
+\input{test/Ocamlary.FunctorTypeOf.tex}
+\input{test/Ocamlary.empty_class.tex}
+\input{test/Ocamlary.one_method_class.tex}
+\input{test/Ocamlary.two_method_class.tex}
+\input{test/Ocamlary.param_class.tex}
+\input{test/Ocamlary.Dep2.tex}
+\input{test/Ocamlary.Dep5.tex}
+\input{test/Ocamlary.Dep7.tex}
+\input{test/Ocamlary.Dep9.tex}
+\input{test/Ocamlary.Dep12.tex}
+\input{test/Ocamlary.Dep13.tex}
+\input{test/Ocamlary.With3.tex}
+\input{test/Ocamlary.With4.tex}
+\input{test/Ocamlary.With7.tex}
diff --git a/test/generators/cases_pre408/latex/Ocamlary.two_method_class.tex b/test/generators/cases_pre408/latex/Ocamlary.two_method_class.tex
new file mode 100644
index 0000000000..0c731deff1
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Ocamlary.two_method_class.tex
@@ -0,0 +1,5 @@
+\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}two\_\allowbreak{}method\_\allowbreak{}class}}\label{container-page-test-module-Ocamlary-class-two+u+method+u+class}%
+\label{container-page-test-module-Ocamlary-class-two+u+method+u+class-method-one}\ocamlcodefragment{\ocamltag{keyword}{method} one : \hyperref[container-page-test-module-Ocamlary-class-one+u+method+u+class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\\
+\label{container-page-test-module-Ocamlary-class-two+u+method+u+class-method-undo}\ocamlcodefragment{\ocamltag{keyword}{method} undo : unit}\\
+
+
diff --git a/test/latex/expect/test_package+ml/Section.tex b/test/generators/cases_pre408/latex/Section.tex
similarity index 84%
rename from test/latex/expect/test_package+ml/Section.tex
rename to test/generators/cases_pre408/latex/Section.tex
index a1c65a43db..ef1961d6db 100644
--- a/test/latex/expect/test_package+ml/Section.tex
+++ b/test/generators/cases_pre408/latex/Section.tex
@@ -1,4 +1,4 @@
-\section{Module \ocamlinlinecode{Section}}\label{container-page-test+u+package+++ml-module-Section}%
+\section{Module \ocamlinlinecode{Section}}\label{container-page-test-module-Section}%
This is the module comment. Eventually, sections won't be allowed in it.
\subsection{Empty section\label{empty-section}}%
@@ -9,7 +9,7 @@ \subsection{Aside only\label{aside-only}}%
Foo bar.
\subsection{Value only\label{value-only}}%
-\label{container-page-test+u+package+++ml-module-Section-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
+\label{container-page-test-module-Section-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
\subsection{Empty section\label{empty-section}}%
\subsection{within a comment\label{within-a-comment}}%
\subsubsection{and one with a nested section\label{and-one-with-a-nested-section}}%
diff --git a/test/latex/expect/test_package+ml/Stop.tex b/test/generators/cases_pre408/latex/Stop.tex
similarity index 52%
rename from test/latex/expect/test_package+ml/Stop.tex
rename to test/generators/cases_pre408/latex/Stop.tex
index 860f392ade..42ea0474b1 100644
--- a/test/latex/expect/test_package+ml/Stop.tex
+++ b/test/generators/cases_pre408/latex/Stop.tex
@@ -1,7 +1,7 @@
-\section{Module \ocamlinlinecode{Stop}}\label{container-page-test+u+package+++ml-module-Stop}%
+\section{Module \ocamlinlinecode{Stop}}\label{container-page-test-module-Stop}%
This test cases exercises stop comments.
-\label{container-page-test+u+package+++ml-module-Stop-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\begin{ocamlindent}This is normal commented text.\end{ocamlindent}%
+\label{container-page-test-module-Stop-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\begin{ocamlindent}This is normal commented text.\end{ocamlindent}%
\medbreak
The next value is \ocamlinlinecode{bar}, and it should be missing from the documentation. There is also an entire module, \ocamlinlinecode{M}, which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope.
@@ -9,9 +9,9 @@ \section{Module \ocamlinlinecode{Stop}}\label{container-page-test+u+package+++ml
Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module.
-\label{container-page-test+u+package+++ml-module-Stop-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Stop-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Stop-module-N-val-quux}\ocamlcodefragment{\ocamltag{keyword}{val} quux : int}\\
+\label{container-page-test-module-Stop-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Stop-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Stop-module-N-val-quux}\ocamlcodefragment{\ocamltag{keyword}{val} quux : int}\\
\end{ocamlindent}%
\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Stop-val-lol}\ocamlcodefragment{\ocamltag{keyword}{val} lol : int}\\
+\label{container-page-test-module-Stop-val-lol}\ocamlcodefragment{\ocamltag{keyword}{val} lol : int}\\
diff --git a/test/generators/cases_pre408/latex/Stop_dead_link_doc.tex b/test/generators/cases_pre408/latex/Stop_dead_link_doc.tex
new file mode 100644
index 0000000000..56bc6f5fc7
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Stop_dead_link_doc.tex
@@ -0,0 +1,28 @@
+\section{Module \ocamlinlinecode{Stop\_\allowbreak{}dead\_\allowbreak{}link\_\allowbreak{}doc}}\label{container-page-test-module-Stop+u+dead+u+link+u+doc}%
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-foo}\ocamlcodefragment{\ocamltag{keyword}{type} foo = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}}}\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-foo.Bar}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-bar}\ocamlcodefragment{\ocamltag{keyword}{type} bar = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field : \hyperref[container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}};\allowbreak{}}\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-bar.field}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-bar.Bar}\\
+\end{ocamlindent}%
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-foo+u+}\ocamlcodefragment{\ocamltag{keyword}{type} foo\_\allowbreak{} = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}} \ocamltag{keyword}{of} int * \hyperref[container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} * int}\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-foo+u+.Bar+u+}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-bar+u+}\ocamlcodefragment{\ocamltag{keyword}{type} bar\_\allowbreak{} = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Stop+u+dead+u+link+u+doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} option}\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-bar+u+.Bar+u++u+}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-another+u+foo}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo}\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-another+u+bar}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar}\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-another+u+foo+u+}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo\_\allowbreak{}}\\
+\label{container-page-test-module-Stop+u+dead+u+link+u+doc-type-another+u+bar+u+}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar\_\allowbreak{}}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Toplevel_comments.Alias.tex b/test/generators/cases_pre408/latex/Toplevel_comments.Alias.tex
new file mode 100644
index 0000000000..7b5761375d
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Toplevel_comments.Alias.tex
@@ -0,0 +1,8 @@
+\section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}Alias}}\label{container-page-test-module-Toplevel+u+comments-module-Alias}%
+Doc of \ocamlinlinecode{Alias}.
+
+Doc of \ocamlinlinecode{T}, part 2.
+
+\label{container-page-test-module-Toplevel+u+comments-module-Alias-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Toplevel_comments.c1.tex b/test/generators/cases_pre408/latex/Toplevel_comments.c1.tex
new file mode 100644
index 0000000000..a16a53ae82
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Toplevel_comments.c1.tex
@@ -0,0 +1,7 @@
+\section{Class \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}c1}}\label{container-page-test-module-Toplevel+u+comments-class-c1}%
+Doc of \ocamlinlinecode{c1}, part 1.
+
+Doc of \ocamlinlinecode{c1}, part 2.
+
+
+
diff --git a/test/generators/cases_pre408/latex/Toplevel_comments.c2.tex b/test/generators/cases_pre408/latex/Toplevel_comments.c2.tex
new file mode 100644
index 0000000000..9465b7b3b0
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Toplevel_comments.c2.tex
@@ -0,0 +1,7 @@
+\section{Class \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}c2}}\label{container-page-test-module-Toplevel+u+comments-class-c2}%
+Doc of \ocamlinlinecode{c2}.
+
+Doc of \ocamlinlinecode{ct}, part 2.
+
+
+
diff --git a/test/generators/cases_pre408/latex/Toplevel_comments.tex b/test/generators/cases_pre408/latex/Toplevel_comments.tex
new file mode 100644
index 0000000000..b0203c849b
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Toplevel_comments.tex
@@ -0,0 +1,45 @@
+\section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments}}\label{container-page-test-module-Toplevel+u+comments}%
+A doc comment at the beginning of a module is considered to be that module's doc.
+
+\label{container-page-test-module-Toplevel+u+comments-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Toplevel+u+comments-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{T}, part 1.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-Include+u+inline}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Toplevel+u+comments-module-Include+u+inline]{\ocamlinlinecode{Include\_\allowbreak{}inline}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}\label{container-page-test-module-Toplevel+u+comments-module-Include+u+inline-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{T}, part 2.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-Include+u+inline'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Toplevel+u+comments-module-Include+u+inline']{\ocamlinlinecode{Include\_\allowbreak{}inline'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}part 3\ocamltag{keyword}{include} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}\label{container-page-test-module-Toplevel+u+comments-module-Include+u+inline'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{Include\_\allowbreak{}inline}, part 1.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-type-Include+u+inline+u+T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-Include+u+inline+u+T]{\ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}\label{container-page-test-module-Toplevel+u+comments-module-type-Include+u+inline+u+T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{T}, part 2.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-type-Include+u+inline+u+T'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-Include+u+inline+u+T']{\ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}part 3\ocamltag{keyword}{include} \hyperref[container-page-test-module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}\label{container-page-test-module-Toplevel+u+comments-module-type-Include+u+inline+u+T'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T'}, part 1.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Toplevel+u+comments-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{M}\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Toplevel+u+comments-module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{M'} from outside\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-M''}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Toplevel+u+comments-module-M'']{\ocamlinlinecode{M''}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{M''}, part 1.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-module-Alias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test-module-Toplevel+u+comments-module-Alias]{\ocamlinlinecode{Alias}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}}\begin{ocamlindent}Doc of \ocamlinlinecode{Alias}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-class-c1}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Toplevel+u+comments-class-c1]{\ocamlinlinecode{c1}}}\ocamlcodefragment{ : int \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{c1}, part 1.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-class-type-ct}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Toplevel+u+comments-class-type-ct]{\ocamlinlinecode{ct}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{ct}, part 1.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Toplevel+u+comments-class-c2}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test-module-Toplevel+u+comments-class-c2]{\ocamlinlinecode{c2}}}\ocamlcodefragment{ : \hyperref[container-page-test-module-Toplevel+u+comments-class-type-ct]{\ocamlinlinecode{ct}}}\begin{ocamlindent}Doc of \ocamlinlinecode{c2}.\end{ocamlindent}%
+\medbreak
+
+\input{test/Toplevel_comments.Alias.tex}
+\input{test/Toplevel_comments.c1.tex}
+\input{test/Toplevel_comments.c2.tex}
diff --git a/test/generators/cases_pre408/latex/Type.tex b/test/generators/cases_pre408/latex/Type.tex
new file mode 100644
index 0000000000..dfd45f4ab9
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Type.tex
@@ -0,0 +1,124 @@
+\section{Module \ocamlinlinecode{Type}}\label{container-page-test-module-Type}%
+\label{container-page-test-module-Type-type-abstract}\ocamlcodefragment{\ocamltag{keyword}{type} abstract}\begin{ocamlindent}Some \emph{documentation}.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Type-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = int}\\
+\label{container-page-test-module-Type-type-private+u+}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{} = \ocamltag{keyword}{private} int}\\
+\label{container-page-test-module-Type-type-constructor}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constructor = \ocamltag{type-var}{'a}}\\
+\label{container-page-test-module-Type-type-arrow}\ocamlcodefragment{\ocamltag{keyword}{type} arrow = int \ocamltag{arrow}{$\rightarrow$} int}\\
+\label{container-page-test-module-Type-type-higher+u+order}\ocamlcodefragment{\ocamltag{keyword}{type} higher\_\allowbreak{}order = (int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\
+\label{container-page-test-module-Type-type-labeled}\ocamlcodefragment{\ocamltag{keyword}{type} labeled = l:int \ocamltag{arrow}{$\rightarrow$} int}\\
+\label{container-page-test-module-Type-type-optional}\ocamlcodefragment{\ocamltag{keyword}{type} optional = ?l:int \ocamltag{arrow}{$\rightarrow$} int}\\
+\label{container-page-test-module-Type-type-labeled+u+higher+u+order}\ocamlcodefragment{\ocamltag{keyword}{type} labeled\_\allowbreak{}higher\_\allowbreak{}order = (l:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (?l:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\
+\label{container-page-test-module-Type-type-pair}\ocamlcodefragment{\ocamltag{keyword}{type} pair = int * int}\\
+\label{container-page-test-module-Type-type-parens+u+dropped}\ocamlcodefragment{\ocamltag{keyword}{type} parens\_\allowbreak{}dropped = int * int}\\
+\label{container-page-test-module-Type-type-triple}\ocamlcodefragment{\ocamltag{keyword}{type} triple = int * int * int}\\
+\label{container-page-test-module-Type-type-nested+u+pair}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}pair = (int * int) * int}\\
+\label{container-page-test-module-Type-type-instance}\ocamlcodefragment{\ocamltag{keyword}{type} instance = int \hyperref[container-page-test-module-Type-type-constructor]{\ocamlinlinecode{constructor}}}\\
+\label{container-page-test-module-Type-type-long}\ocamlcodefragment{\ocamltag{keyword}{type} long = \hyperref[container-page-test-module-Type-type-labeled+u+higher+u+order]{\ocamlinlinecode{labeled\_\allowbreak{}higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} [ `Bar | `Baz of \hyperref[container-page-test-module-Type-type-triple]{\ocamlinlinecode{triple}} ] \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Type-type-pair]{\ocamlinlinecode{pair}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Type-type-labeled]{\ocamlinlinecode{labeled}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Type-type-higher+u+order]{\ocamlinlinecode{higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} (string \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (int,\allowbreak{} float,\allowbreak{} char,\allowbreak{} string,\allowbreak{} char,\allowbreak{} unit) \hyperref[xref-unresolved]{\ocamlinlinecode{CamlinternalFormatBasics}}.\allowbreak{}fmtty \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Type-type-nested+u+pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Type-type-arrow]{\ocamlinlinecode{arrow}} \ocamltag{arrow}{$\rightarrow$} string \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test-module-Type-type-nested+u+pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} array}\\
+\label{container-page-test-module-Type-type-variant+u+e}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}e = \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test-module-Type-type-variant+u+e.a}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\\
+\label{container-page-test-module-Type-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test-module-Type-type-variant.A}& \\
+\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{container-page-test-module-Type-type-variant.B}& \\
+\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{container-page-test-module-Type-type-variant.C}& foo\\
+\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{container-page-test-module-Type-type-variant.D}& \emph{bar}\\
+\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Type-type-variant+u+e]{\ocamlinlinecode{variant\_\allowbreak{}e}}}\label{container-page-test-module-Type-type-variant.E}& \\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-type-variant+u+c}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}c = \{}\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test-module-Type-type-variant+u+c.a}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\\
+\label{container-page-test-module-Type-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[container-page-test-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test-module-Type-type-gadt.A}\\
+\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[container-page-test-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test-module-Type-type-gadt.B}\\
+\ocamlcodefragment{| \ocamltag{constructor}{C} : \hyperref[container-page-test-module-Type-type-variant+u+c]{\ocamlinlinecode{variant\_\allowbreak{}c}} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[container-page-test-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test-module-Type-type-gadt.C}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-type-degenerate+u+gadt}\ocamlcodefragment{\ocamltag{keyword}{type} degenerate\_\allowbreak{}gadt = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : \hyperref[container-page-test-module-Type-type-degenerate+u+gadt]{\ocamlinlinecode{degenerate\_\allowbreak{}gadt}}}\label{container-page-test-module-Type-type-degenerate+u+gadt.A}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-type-private+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}variant = \ocamltag{keyword}{private} }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test-module-Type-type-private+u+variant.A}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test-module-Type-type-record.a}& \\
+\ocamlinlinecode{\ocamltag{keyword}{mutable} b : int;\allowbreak{}}\label{container-page-test-module-Type-type-record.b}& \\
+\ocamlinlinecode{c : int;\allowbreak{}}\label{container-page-test-module-Type-type-record.c}& foo\\
+\ocamlinlinecode{d : int;\allowbreak{}}\label{container-page-test-module-Type-type-record.d}& \emph{bar}\\
+\ocamlinlinecode{e : a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{}}\label{container-page-test-module-Type-type-record.e}& \\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{\}}\\
+\label{container-page-test-module-Type-type-polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test-module-Type-type-polymorphic+u+variant.A}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} int}\label{container-page-test-module-Type-type-polymorphic+u+variant.B}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`C \ocamltag{keyword}{of} int * unit}\label{container-page-test-module-Type-type-polymorphic+u+variant.C}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`D}\label{container-page-test-module-Type-type-polymorphic+u+variant.D}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Type-type-polymorphic+u+variant+u+extension}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant\_\allowbreak{}extension = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[container-page-test-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{container-page-test-module-Type-type-polymorphic+u+variant+u+extension.polymorphic+u+variant}\\
+\ocamlinlinecode{| }\ocamlinlinecode{`E}\label{container-page-test-module-Type-type-polymorphic+u+variant+u+extension.E}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Type-type-nested+u+polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}polymorphic\_\allowbreak{}variant = [ }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A \ocamltag{keyword}{of} [ `B | `C ]}\label{container-page-test-module-Type-type-nested+u+polymorphic+u+variant.A}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Type-type-private+u+extenion#row}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}extenion\#row}\\
+\label{container-page-test-module-Type-type-private+u+extenion}\ocamlcodefragment{\ocamltag{keyword}{and} private\_\allowbreak{}extenion = \ocamltag{keyword}{private} [> }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[container-page-test-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{container-page-test-module-Type-type-private+u+extenion.polymorphic+u+variant}\\
+\end{ocamltabular}%
+\\
+\ocamlcodefragment{ ]}\\
+\label{container-page-test-module-Type-type-object+u+}\ocamlcodefragment{\ocamltag{keyword}{type} object\_\allowbreak{} = < a : int;\allowbreak{} b : int;\allowbreak{} c : int;\allowbreak{} >}\\
+\label{container-page-test-module-Type-module-type-X}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Type-module-type-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test-module-Type-module-type-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
+\label{container-page-test-module-Type-module-type-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
+\end{ocamlindent}%
+\ocamlcodefragment{\ocamltag{keyword}{end}}\\
+\label{container-page-test-module-Type-type-module+u+}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{} = (\ocamltag{keyword}{module} \hyperref[container-page-test-module-Type-module-type-X]{\ocamlinlinecode{X}})}\\
+\label{container-page-test-module-Type-type-module+u+substitution}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{}substitution = (\ocamltag{keyword}{module} \hyperref[container-page-test-module-Type-module-type-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Type-module-type-X-type-t]{\ocamlinlinecode{t}} = int \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[container-page-test-module-Type-module-type-X-type-u]{\ocamlinlinecode{u}} = unit)}\\
+\label{container-page-test-module-Type-type-covariant}\ocamlcodefragment{\ocamltag{keyword}{type} +'a covariant}\\
+\label{container-page-test-module-Type-type-contravariant}\ocamlcodefragment{\ocamltag{keyword}{type} -'a contravariant}\\
+\label{container-page-test-module-Type-type-bivariant}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} bivariant = int}\\
+\label{container-page-test-module-Type-type-binary}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) binary}\\
+\label{container-page-test-module-Type-type-using+u+binary}\ocamlcodefragment{\ocamltag{keyword}{type} using\_\allowbreak{}binary = (int,\allowbreak{} int) \hyperref[container-page-test-module-Type-type-binary]{\ocamlinlinecode{binary}}}\\
+\label{container-page-test-module-Type-type-name}\ocamlcodefragment{\ocamltag{keyword}{type} 'custom name}\\
+\label{container-page-test-module-Type-type-constrained}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constrained = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int}\\
+\label{container-page-test-module-Type-type-exact+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [ `A | `B of int ]}\\
+\label{container-page-test-module-Type-type-lower+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `A | `B of int ]}\\
+\label{container-page-test-module-Type-type-any+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> ]}\\
+\label{container-page-test-module-Type-type-upper+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a upper\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< `A | `B of int ]}\\
+\label{container-page-test-module-Type-type-named+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a named\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< \hyperref[container-page-test-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}} ]}\\
+\label{container-page-test-module-Type-type-exact+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int;\allowbreak{} b : int;\allowbreak{} >}\\
+\label{container-page-test-module-Type-type-lower+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int;\allowbreak{} b : int;\allowbreak{} .\allowbreak{}.\allowbreak{} >}\\
+\label{container-page-test-module-Type-type-poly+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{} >}\\
+\label{container-page-test-module-Type-type-double+u+constrained}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) double\_\allowbreak{}constrained = \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int \ocamltag{keyword}{constraint} \ocamltag{type-var}{'b} = unit}\\
+\label{container-page-test-module-Type-type-as+u+}\ocamlcodefragment{\ocamltag{keyword}{type} as\_\allowbreak{} = int \ocamltag{keyword}{as} 'a * \ocamltag{type-var}{'a}}\\
+\label{container-page-test-module-Type-type-extensible}\ocamlcodefragment{\ocamltag{keyword}{type} extensible = .\allowbreak{}.\allowbreak{}}\\
+\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test-module-Type-type-extensible]{\ocamlinlinecode{extensible}} += }\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Extension}}\label{container-page-test-module-Type-extension-Extension}& Documentation for \hyperref[container-page-test-module-Type-extension-Extension]{\ocamlinlinecode{\ocamlinlinecode{Extension}}[p\pageref*{container-page-test-module-Type-extension-Extension}]}.\\
+\ocamlcodefragment{| \ocamltag{extension}{Another\_\allowbreak{}extension}}\label{container-page-test-module-Type-extension-Another+u+extension}& Documentation for \hyperref[container-page-test-module-Type-extension-Another+u+extension]{\ocamlinlinecode{\ocamlinlinecode{Another\_\allowbreak{}extension}}[p\pageref*{container-page-test-module-Type-extension-Another+u+extension}]}.\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{type} mutually = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Type-type-recursive]{\ocamlinlinecode{recursive}}}\label{container-page-test-module-Type-type-mutually.A}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{and} recursive = }\\
+\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} \hyperref[container-page-test-module-Type-type-mutually]{\ocamlinlinecode{mutually}}}\label{container-page-test-module-Type-type-recursive.B}\\
+\end{ocamltabular}%
+\\
+\label{container-page-test-module-Type-exception-Foo}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Foo} \ocamltag{keyword}{of} int * int}\\
+
+
diff --git a/test/generators/cases_pre408/latex/Val.tex b/test/generators/cases_pre408/latex/Val.tex
new file mode 100644
index 0000000000..637934ba74
--- /dev/null
+++ b/test/generators/cases_pre408/latex/Val.tex
@@ -0,0 +1,8 @@
+\section{Module \ocamlinlinecode{Val}}\label{container-page-test-module-Val}%
+\label{container-page-test-module-Val-val-documented}\ocamlcodefragment{\ocamltag{keyword}{val} documented : unit}\begin{ocamlindent}Foo.\end{ocamlindent}%
+\medbreak
+\label{container-page-test-module-Val-val-undocumented}\ocamlcodefragment{\ocamltag{keyword}{val} undocumented : unit}\\
+\label{container-page-test-module-Val-val-documented+u+above}\ocamlcodefragment{\ocamltag{keyword}{val} documented\_\allowbreak{}above : unit}\begin{ocamlindent}Bar.\end{ocamlindent}%
+\medbreak
+
+
diff --git a/test/generators/cases_pre408/latex/dune b/test/generators/cases_pre408/latex/dune
new file mode 100644
index 0000000000..11244a7204
--- /dev/null
+++ b/test/generators/cases_pre408/latex/dune
@@ -0,0 +1 @@
+(include latex.dune.inc)
diff --git a/test/generators/cases_pre408/latex/gen_latex/dune b/test/generators/cases_pre408/latex/gen_latex/dune
new file mode 100644
index 0000000000..a8328f0f5d
--- /dev/null
+++ b/test/generators/cases_pre408/latex/gen_latex/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_latex)
+ (libraries latex_t_rule)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_pre408/latex/gen_latex/gen_latex.ml b/test/generators/cases_pre408/latex/gen_latex/gen_latex.ml
new file mode 100644
index 0000000000..2bc13dfd01
--- /dev/null
+++ b/test/generators/cases_pre408/latex/gen_latex/gen_latex.ml
@@ -0,0 +1,6 @@
+let () =
+ let stanzas =
+ Gen_backend.gen_backend_rules "latex" Latex_t_rule.latex_target_rule
+ Gen_backend.files "4.10"
+ in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_pre408/latex/latex.dune.inc b/test/generators/cases_pre408/latex/latex.dune.inc
new file mode 100644
index 0000000000..be7cb839dc
--- /dev/null
+++ b/test/generators/cases_pre408/latex/latex.dune.inc
@@ -0,0 +1,784 @@
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../alias.odocl})
+ (with-stdout-to
+ Alias.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Alias.tex'")))
+ (with-stdout-to
+ Alias.X.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Alias.X.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.tex Alias.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.X.tex Alias.X.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../bugs.odocl})
+ (with-stdout-to
+ Bugs.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Bugs.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs.tex Bugs.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../bugs_pre_410.odocl})
+ (with-stdout-to
+ Bugs_pre_410.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Bugs_pre_410.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_pre_410.tex Bugs_pre_410.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../class.odocl})
+ (with-stdout-to
+ Class.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Class.tex'")))
+ (with-stdout-to
+ Class.mutually'.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Class.mutually'\\''.tex'")))
+ (with-stdout-to
+ Class.recursive'.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Class.recursive'\\''.tex'")))
+ (with-stdout-to
+ Class.empty_virtual'.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Class.empty_virtual'\\''.tex'")))
+ (with-stdout-to
+ Class.polymorphic'.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Class.polymorphic'\\''.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.tex Class.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.mutually'.tex Class.mutually'.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.recursive'.tex Class.recursive'.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.empty_virtual'.tex Class.empty_virtual'.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.polymorphic'.tex Class.polymorphic'.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../external.odocl})
+ (with-stdout-to
+ External.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/External.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff External.tex External.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../functor.odocl})
+ (with-stdout-to
+ Functor.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor.tex'")))
+ (with-stdout-to
+ Functor.F1.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor.F1.tex'")))
+ (with-stdout-to
+ Functor.F2.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor.F2.tex'")))
+ (with-stdout-to
+ Functor.F3.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor.F3.tex'")))
+ (with-stdout-to
+ Functor.F4.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor.F4.tex'")))
+ (with-stdout-to
+ Functor.F5.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor.F5.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.tex Functor.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F1.tex Functor.F1.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F2.tex Functor.F2.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F3.tex Functor.F3.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F4.tex Functor.F4.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F5.tex Functor.F5.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../functor2.odocl})
+ (with-stdout-to
+ Functor2.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor2.tex'")))
+ (with-stdout-to
+ Functor2.X.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Functor2.X.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor2.tex Functor2.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor2.X.tex Functor2.X.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../include.odocl})
+ (with-stdout-to
+ Include.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Include.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include.tex Include.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../include2.odocl})
+ (with-stdout-to
+ Include2.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Include2.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.tex Include2.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../include_sections.odocl})
+ (with-stdout-to
+ Include_sections.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Include_sections.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include_sections.tex Include_sections.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../interlude.odocl})
+ (with-stdout-to
+ Interlude.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Interlude.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Interlude.tex Interlude.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../markup.odocl})
+ (with-stdout-to
+ Markup.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Markup.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Markup.tex Markup.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../page-mld.odocl})
+ (with-stdout-to
+ mld.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/mld.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff mld.tex mld.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../module.odocl})
+ (with-stdout-to
+ Module.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Module.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.tex Module.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../nested.odocl})
+ (with-stdout-to
+ Nested.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Nested.tex'")))
+ (with-stdout-to
+ Nested.F.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Nested.F.tex'")))
+ (with-stdout-to
+ Nested.z.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Nested.z.tex'")))
+ (with-stdout-to
+ Nested.inherits.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Nested.inherits.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.tex Nested.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.F.tex Nested.F.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.z.tex Nested.z.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.inherits.tex Nested.inherits.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../ocamlary.odocl})
+ (with-stdout-to
+ Ocamlary.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.tex'")))
+ (with-stdout-to
+ Ocamlary.ModuleWithSignature.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.ModuleWithSignature.tex'")))
+ (with-stdout-to
+ Ocamlary.ModuleWithSignatureAlias.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.ModuleWithSignatureAlias.tex'")))
+ (with-stdout-to
+ Ocamlary.Recollection.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Recollection.tex'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.FunctorTypeOf.tex'")))
+ (with-stdout-to
+ Ocamlary.empty_class.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.empty_class.tex'")))
+ (with-stdout-to
+ Ocamlary.one_method_class.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.one_method_class.tex'")))
+ (with-stdout-to
+ Ocamlary.two_method_class.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.two_method_class.tex'")))
+ (with-stdout-to
+ Ocamlary.param_class.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.param_class.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep2.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep2.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep5.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep5.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep5.Z.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep5.Z.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep7.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep7.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep7.M.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep7.M.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep9.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep9.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep12.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep12.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep13.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep13.tex'")))
+ (with-stdout-to
+ Ocamlary.Dep13.c.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.Dep13.c.tex'")))
+ (with-stdout-to
+ Ocamlary.With3.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.With3.tex'")))
+ (with-stdout-to
+ Ocamlary.With3.N.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.With3.N.tex'")))
+ (with-stdout-to
+ Ocamlary.With4.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.With4.tex'")))
+ (with-stdout-to
+ Ocamlary.With4.N.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.With4.N.tex'")))
+ (with-stdout-to
+ Ocamlary.With7.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Ocamlary.With7.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.tex Ocamlary.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.ModuleWithSignature.tex
+ Ocamlary.ModuleWithSignature.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.ModuleWithSignatureAlias.tex
+ Ocamlary.ModuleWithSignatureAlias.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Recollection.tex Ocamlary.Recollection.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.FunctorTypeOf.tex Ocamlary.FunctorTypeOf.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.empty_class.tex Ocamlary.empty_class.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.one_method_class.tex Ocamlary.one_method_class.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.two_method_class.tex Ocamlary.two_method_class.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.param_class.tex Ocamlary.param_class.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep2.tex Ocamlary.Dep2.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep5.tex Ocamlary.Dep5.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep5.Z.tex Ocamlary.Dep5.Z.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep7.tex Ocamlary.Dep7.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep7.M.tex Ocamlary.Dep7.M.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep9.tex Ocamlary.Dep9.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep12.tex Ocamlary.Dep12.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep13.tex Ocamlary.Dep13.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep13.c.tex Ocamlary.Dep13.c.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With3.tex Ocamlary.With3.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With3.N.tex Ocamlary.With3.N.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With4.tex Ocamlary.With4.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With4.N.tex Ocamlary.With4.N.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With7.tex Ocamlary.With7.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../section.odocl})
+ (with-stdout-to
+ Section.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Section.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Section.tex Section.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../stop.odocl})
+ (with-stdout-to
+ Stop.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Stop.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop.tex Stop.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../stop_dead_link_doc.odocl})
+ (with-stdout-to
+ Stop_dead_link_doc.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Stop_dead_link_doc.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop_dead_link_doc.tex Stop_dead_link_doc.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../toplevel_comments.odocl})
+ (with-stdout-to
+ Toplevel_comments.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Toplevel_comments.tex'")))
+ (with-stdout-to
+ Toplevel_comments.Alias.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Toplevel_comments.Alias.tex'")))
+ (with-stdout-to
+ Toplevel_comments.c1.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Toplevel_comments.c1.tex'")))
+ (with-stdout-to
+ Toplevel_comments.c2.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Toplevel_comments.c2.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.tex Toplevel_comments.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.Alias.tex Toplevel_comments.Alias.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.c1.tex Toplevel_comments.c1.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.c2.tex Toplevel_comments.c2.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../type.odocl})
+ (with-stdout-to
+ Type.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Type.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Type.tex Type.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc latex-generate -o latex.gen %{dep:../val.odocl})
+ (with-stdout-to
+ Val.tex.gen
+ (progn
+ (system "cat 'latex.gen/test/Val.tex'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Val.tex Val.tex.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
diff --git a/test/latex/expect/test_package+ml/mld.tex b/test/generators/cases_pre408/latex/mld.tex
similarity index 89%
rename from test/latex/expect/test_package+ml/mld.tex
rename to test/generators/cases_pre408/latex/mld.tex
index cd09dd64c4..5f60cc49f2 100644
--- a/test/latex/expect/test_package+ml/mld.tex
+++ b/test/generators/cases_pre408/latex/mld.tex
@@ -1,4 +1,4 @@
-\section{Mld Page\label{mld-page}}\label{container-page-test+u+package+++ml-page-mld}%
+\section{Mld Page\label{mld-page}}\label{container-page-test-page-mld}%
This is an \ocamlinlinecode{.\allowbreak{}mld} file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do.
It will have a TOC generated from section headings.
diff --git a/test/generators/cases_pre408/link.dune.inc b/test/generators/cases_pre408/link.dune.inc
new file mode 100644
index 0000000000..2119e57a2f
--- /dev/null
+++ b/test/generators/cases_pre408/link.dune.inc
@@ -0,0 +1,506 @@
+(rule
+ (target alias.cmt)
+ (deps cases/alias.ml)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target alias.odoc)
+ (deps alias.cmt)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target alias.odocl)
+ (deps alias.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target bugs.cmt)
+ (deps cases/bugs.ml)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target bugs.odoc)
+ (deps bugs.cmt)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target bugs.odocl)
+ (deps bugs.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target bugs_pre_410.cmt)
+ (deps cases/bugs_pre_410.ml)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target bugs_pre_410.odoc)
+ (deps bugs_pre_410.cmt)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target bugs_pre_410.odocl)
+ (deps bugs_pre_410.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target class.cmti)
+ (deps cases/class.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target class.odoc)
+ (deps class.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target class.odocl)
+ (deps class.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target external.cmti)
+ (deps cases/external.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target external.odoc)
+ (deps external.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target external.odocl)
+ (deps external.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target functor.cmti)
+ (deps cases/functor.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target functor.odoc)
+ (deps functor.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target functor.odocl)
+ (deps functor.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target functor2.cmti)
+ (deps cases/functor2.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target functor2.odoc)
+ (deps functor2.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target functor2.odocl)
+ (deps functor2.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target include.cmti)
+ (deps cases/include.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target include.odoc)
+ (deps include.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target include.odocl)
+ (deps include.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target include2.cmt)
+ (deps cases/include2.ml)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target include2.odoc)
+ (deps include2.cmt)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target include2.odocl)
+ (deps include2.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target include_sections.cmti)
+ (deps cases/include_sections.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target include_sections.odoc)
+ (deps include_sections.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target include_sections.odocl)
+ (deps include_sections.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target interlude.cmti)
+ (deps cases/interlude.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target interlude.odoc)
+ (deps interlude.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target interlude.odocl)
+ (deps interlude.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target markup.cmti)
+ (deps cases/markup.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target markup.odoc)
+ (deps markup.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target markup.odocl)
+ (deps markup.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target page-mld.odoc)
+ (deps cases/mld.mld)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target page-mld.odocl)
+ (deps page-mld.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target module.cmti)
+ (deps cases/module.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target module.odoc)
+ (deps module.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target module.odocl)
+ (deps module.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target nested.cmti)
+ (deps cases/nested.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target nested.odoc)
+ (deps nested.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target nested.odocl)
+ (deps nested.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target ocamlary.cmti)
+ (deps cases/ocamlary.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target ocamlary.odoc)
+ (deps ocamlary.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target ocamlary.odocl)
+ (deps ocamlary.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target section.cmti)
+ (deps cases/section.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target section.odoc)
+ (deps section.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target section.odocl)
+ (deps section.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target stop.cmti)
+ (deps cases/stop.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target stop.odoc)
+ (deps stop.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target stop.odocl)
+ (deps stop.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target stop_dead_link_doc.cmti)
+ (deps cases/stop_dead_link_doc.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target stop_dead_link_doc.odoc)
+ (deps stop_dead_link_doc.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target stop_dead_link_doc.odocl)
+ (deps stop_dead_link_doc.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target toplevel_comments.cmti)
+ (deps cases/toplevel_comments.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target toplevel_comments.odoc)
+ (deps toplevel_comments.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target toplevel_comments.odocl)
+ (deps toplevel_comments.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target type.cmti)
+ (deps cases/type.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target type.odoc)
+ (deps type.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target type.odocl)
+ (deps type.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(rule
+ (target val.cmti)
+ (deps cases/val.mli)
+ (action
+ (run ocamlc -c -bin-annot -o %{target} %{deps})))
+
+(rule
+ (target val.odoc)
+ (deps val.cmti)
+ (action
+ (run odoc compile --pkg test -o %{target} %{deps})))
+
+(rule
+ (target val.odocl)
+ (deps val.odoc)
+ (action
+ (run odoc link -o %{target} %{deps})))
+
+(subdir
+ html
+ (rule
+ (with-stdout-to
+ html.dune.inc.gen
+ (pipe-stdout
+ (run
+ gen_html/gen_html.exe
+ %{dep:../alias.odocl}
+ %{dep:../bugs.odocl}
+ %{dep:../bugs_pre_410.odocl}
+ %{dep:../class.odocl}
+ %{dep:../external.odocl}
+ %{dep:../functor.odocl}
+ %{dep:../functor2.odocl}
+ %{dep:../include.odocl}
+ %{dep:../include2.odocl}
+ %{dep:../include_sections.odocl}
+ %{dep:../interlude.odocl}
+ %{dep:../markup.odocl}
+ %{dep:../page-mld.odocl}
+ %{dep:../module.odocl}
+ %{dep:../nested.odocl}
+ %{dep:../ocamlary.odocl}
+ %{dep:../section.odocl}
+ %{dep:../stop.odocl}
+ %{dep:../stop_dead_link_doc.odocl}
+ %{dep:../toplevel_comments.odocl}
+ %{dep:../type.odocl}
+ %{dep:../val.odocl})
+ (run dune format-dune-file)))))
+
+(subdir
+ latex
+ (rule
+ (with-stdout-to
+ latex.dune.inc.gen
+ (pipe-stdout
+ (run
+ gen_latex/gen_latex.exe
+ %{dep:../alias.odocl}
+ %{dep:../bugs.odocl}
+ %{dep:../bugs_pre_410.odocl}
+ %{dep:../class.odocl}
+ %{dep:../external.odocl}
+ %{dep:../functor.odocl}
+ %{dep:../functor2.odocl}
+ %{dep:../include.odocl}
+ %{dep:../include2.odocl}
+ %{dep:../include_sections.odocl}
+ %{dep:../interlude.odocl}
+ %{dep:../markup.odocl}
+ %{dep:../page-mld.odocl}
+ %{dep:../module.odocl}
+ %{dep:../nested.odocl}
+ %{dep:../ocamlary.odocl}
+ %{dep:../section.odocl}
+ %{dep:../stop.odocl}
+ %{dep:../stop_dead_link_doc.odocl}
+ %{dep:../toplevel_comments.odocl}
+ %{dep:../type.odocl}
+ %{dep:../val.odocl})
+ (run dune format-dune-file)))))
+
+(subdir
+ man
+ (rule
+ (with-stdout-to
+ man.dune.inc.gen
+ (pipe-stdout
+ (run
+ gen_man/gen_man.exe
+ %{dep:../alias.odocl}
+ %{dep:../bugs.odocl}
+ %{dep:../bugs_pre_410.odocl}
+ %{dep:../class.odocl}
+ %{dep:../external.odocl}
+ %{dep:../functor.odocl}
+ %{dep:../functor2.odocl}
+ %{dep:../include.odocl}
+ %{dep:../include2.odocl}
+ %{dep:../include_sections.odocl}
+ %{dep:../interlude.odocl}
+ %{dep:../markup.odocl}
+ %{dep:../page-mld.odocl}
+ %{dep:../module.odocl}
+ %{dep:../nested.odocl}
+ %{dep:../ocamlary.odocl}
+ %{dep:../section.odocl}
+ %{dep:../stop.odocl}
+ %{dep:../stop_dead_link_doc.odocl}
+ %{dep:../toplevel_comments.odocl}
+ %{dep:../type.odocl}
+ %{dep:../val.odocl})
+ (run dune format-dune-file)))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff html/html.dune.inc html/html.dune.inc.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff latex/latex.dune.inc latex/latex.dune.inc.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff man/man.dune.inc man/man.dune.inc.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
diff --git a/test/man/expect/test_package+ml/Alias.3o b/test/generators/cases_pre408/man/Alias.3o
similarity index 91%
rename from test/man/expect/test_package+ml/Alias.3o
rename to test/generators/cases_pre408/man/Alias.3o
index d4b883d5bf..379f962f82 100644
--- a/test/man/expect/test_package+ml/Alias.3o
+++ b/test/generators/cases_pre408/man/Alias.3o
@@ -1,7 +1,7 @@
.TH Alias 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Alias
+test\.Alias
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Alias.Foo__X.3o b/test/generators/cases_pre408/man/Alias.Foo__X.3o
new file mode 100644
index 0000000000..ce2039246f
--- /dev/null
+++ b/test/generators/cases_pre408/man/Alias.Foo__X.3o
@@ -0,0 +1,20 @@
+
+.TH Foo__X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Alias\.Foo__X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Alias\.Foo__X\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = int
+.fi
+.br
+.ti +2
+Module Foo__X documentation\. This should appear in the documentation for the alias to this module 'X'
+.nf
+
diff --git a/test/man/expect/test_package+ml/Alias.X.3o b/test/generators/cases_pre408/man/Alias.X.3o
similarity index 91%
rename from test/man/expect/test_package+ml/Alias.X.3o
rename to test/generators/cases_pre408/man/Alias.X.3o
index 53b5e1bf7d..31ca5f9370 100644
--- a/test/man/expect/test_package+ml/Alias.X.3o
+++ b/test/generators/cases_pre408/man/Alias.X.3o
@@ -1,7 +1,7 @@
.TH X 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Alias\.X
+test\.Alias\.X
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Bugs.3o b/test/generators/cases_pre408/man/Bugs.3o
similarity index 94%
rename from test/man/expect/test_package+ml/Bugs.3o
rename to test/generators/cases_pre408/man/Bugs.3o
index d9d2b60fd2..fe21b9e6be 100644
--- a/test/man/expect/test_package+ml/Bugs.3o
+++ b/test/generators/cases_pre408/man/Bugs.3o
@@ -1,7 +1,7 @@
.TH Bugs 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Bugs
+test\.Bugs
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Bugs_pre_410.3o b/test/generators/cases_pre408/man/Bugs_pre_410.3o
similarity index 81%
rename from test/man/expect/test_package+ml/Bugs_pre_410.3o
rename to test/generators/cases_pre408/man/Bugs_pre_410.3o
index 13eb8be101..beeb84d5e7 100644
--- a/test/man/expect/test_package+ml/Bugs_pre_410.3o
+++ b/test/generators/cases_pre408/man/Bugs_pre_410.3o
@@ -1,7 +1,7 @@
.TH Bugs_pre_410 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Bugs_pre_410
+test\.Bugs_pre_410
.SH Synopsis
.sp
.in 2
@@ -13,7 +13,7 @@ test_package+ml\.Bugs_pre_410
.nf
\f[CB]type\fR 'a opt' = int option
.sp
-\f[CB]val\fR foo' : ?bar:\f[CB]'a\fR \f[CB]\->\fR unit \f[CB]\->\fR unit
+\f[CB]val\fR foo' : ?bar:int \f[CB]\->\fR unit \f[CB]\->\fR unit
.fi
.br
.ti +2
diff --git a/test/man/expect/test_package+ml/Class.3o b/test/generators/cases_pre408/man/Class.3o
similarity index 96%
rename from test/man/expect/test_package+ml/Class.3o
rename to test/generators/cases_pre408/man/Class.3o
index 0f704875b6..b3704232af 100644
--- a/test/man/expect/test_package+ml/Class.3o
+++ b/test/generators/cases_pre408/man/Class.3o
@@ -1,7 +1,7 @@
.TH Class 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Class
+test\.Class
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Class.empty_virtual'.3o b/test/generators/cases_pre408/man/Class.empty_virtual'.3o
new file mode 100644
index 0000000000..55238a07ca
--- /dev/null
+++ b/test/generators/cases_pre408/man/Class.empty_virtual'.3o
@@ -0,0 +1,14 @@
+
+.TH empty_virtual' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Class\.empty_virtual'
+.SH Synopsis
+.sp
+.in 2
+\fBClass Class\.empty_virtual'\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Class.mutually'.3o b/test/generators/cases_pre408/man/Class.mutually'.3o
new file mode 100644
index 0000000000..46e375be91
--- /dev/null
+++ b/test/generators/cases_pre408/man/Class.mutually'.3o
@@ -0,0 +1,14 @@
+
+.TH mutually' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Class\.mutually'
+.SH Synopsis
+.sp
+.in 2
+\fBClass Class\.mutually'\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Class.polymorphic'.3o b/test/generators/cases_pre408/man/Class.polymorphic'.3o
new file mode 100644
index 0000000000..69abe1722e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Class.polymorphic'.3o
@@ -0,0 +1,14 @@
+
+.TH polymorphic' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Class\.polymorphic'
+.SH Synopsis
+.sp
+.in 2
+\fBClass Class\.polymorphic'\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Class.recursive'.3o b/test/generators/cases_pre408/man/Class.recursive'.3o
new file mode 100644
index 0000000000..1f12de53fe
--- /dev/null
+++ b/test/generators/cases_pre408/man/Class.recursive'.3o
@@ -0,0 +1,14 @@
+
+.TH recursive' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Class\.recursive'
+.SH Synopsis
+.sp
+.in 2
+\fBClass Class\.recursive'\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/man/expect/test_package+ml/External.3o b/test/generators/cases_pre408/man/External.3o
similarity index 88%
rename from test/man/expect/test_package+ml/External.3o
rename to test/generators/cases_pre408/man/External.3o
index ad60ecb72b..39dce4c134 100644
--- a/test/man/expect/test_package+ml/External.3o
+++ b/test/generators/cases_pre408/man/External.3o
@@ -1,7 +1,7 @@
.TH External 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.External
+test\.External
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Functor.3o b/test/generators/cases_pre408/man/Functor.3o
similarity index 96%
rename from test/man/expect/test_package+ml/Functor.3o
rename to test/generators/cases_pre408/man/Functor.3o
index c384b7bf54..0c8359a5e9 100644
--- a/test/man/expect/test_package+ml/Functor.3o
+++ b/test/generators/cases_pre408/man/Functor.3o
@@ -1,7 +1,7 @@
.TH Functor 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Functor
+test\.Functor
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Functor.F1.3o b/test/generators/cases_pre408/man/Functor.F1.3o
similarity index 91%
rename from test/man/expect/test_package+ml/Functor.F1.3o
rename to test/generators/cases_pre408/man/Functor.F1.3o
index 0834feb5d1..93f73d0366 100644
--- a/test/man/expect/test_package+ml/Functor.F1.3o
+++ b/test/generators/cases_pre408/man/Functor.F1.3o
@@ -1,7 +1,7 @@
.TH F1 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Functor\.F1
+test\.Functor\.F1
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Functor.F2.3o b/test/generators/cases_pre408/man/Functor.F2.3o
similarity index 91%
rename from test/man/expect/test_package+ml/Functor.F2.3o
rename to test/generators/cases_pre408/man/Functor.F2.3o
index f236ec8741..effc69506b 100644
--- a/test/man/expect/test_package+ml/Functor.F2.3o
+++ b/test/generators/cases_pre408/man/Functor.F2.3o
@@ -1,7 +1,7 @@
.TH F2 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Functor\.F2
+test\.Functor\.F2
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Functor.F3.3o b/test/generators/cases_pre408/man/Functor.F3.3o
similarity index 91%
rename from test/man/expect/test_package+ml/Functor.F3.3o
rename to test/generators/cases_pre408/man/Functor.F3.3o
index 36ad230b97..9d04463228 100644
--- a/test/man/expect/test_package+ml/Functor.F3.3o
+++ b/test/generators/cases_pre408/man/Functor.F3.3o
@@ -1,7 +1,7 @@
.TH F3 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Functor\.F3
+test\.Functor\.F3
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Functor.F4.3o b/test/generators/cases_pre408/man/Functor.F4.3o
similarity index 91%
rename from test/man/expect/test_package+ml/Functor.F4.3o
rename to test/generators/cases_pre408/man/Functor.F4.3o
index 2f754b4961..8bf47dd588 100644
--- a/test/man/expect/test_package+ml/Functor.F4.3o
+++ b/test/generators/cases_pre408/man/Functor.F4.3o
@@ -1,7 +1,7 @@
.TH F4 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Functor\.F4
+test\.Functor\.F4
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Functor.F5.3o b/test/generators/cases_pre408/man/Functor.F5.3o
new file mode 100644
index 0000000000..a2e57c83dd
--- /dev/null
+++ b/test/generators/cases_pre408/man/Functor.F5.3o
@@ -0,0 +1,23 @@
+
+.TH F5 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Functor\.F5
+.SH Synopsis
+.sp
+.in 2
+\fBModule Functor\.F5\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Functor2.3o b/test/generators/cases_pre408/man/Functor2.3o
new file mode 100644
index 0000000000..d818413b34
--- /dev/null
+++ b/test/generators/cases_pre408/man/Functor2.3o
@@ -0,0 +1,60 @@
+
+.TH Functor2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Functor2
+.SH Synopsis
+.sp
+.in 2
+\fBModule Functor2\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR X (Y : S) (Z : S) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR XF = \f[CB]sig\fR
+.br
+.ti +2
+.sp
+.ti +2
+\fB1\.1 Parameters\fR
+.sp
+.ti +2
+\f[CB]module\fR Y : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR Z : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\fB1\.2 Signature\fR
+.sp
+.ti +2
+\f[CB]type\fR y_t = Y\.t
+.sp
+.ti +2
+\f[CB]type\fR z_t = Z\.t
+.sp
+.ti +2
+\f[CB]type\fR x_t = y_t
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Functor2.X.3o b/test/generators/cases_pre408/man/Functor2.X.3o
new file mode 100644
index 0000000000..f8cc2cae4a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Functor2.X.3o
@@ -0,0 +1,41 @@
+
+.TH X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Functor2\.X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Functor2\.X\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR Y : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR Z : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]type\fR y_t = Y\.t
+.sp
+\f[CB]type\fR z_t = Z\.t
+.sp
+\f[CB]type\fR x_t = y_t
diff --git a/test/man/expect/test_package+ml/Include.3o b/test/generators/cases_pre408/man/Include.3o
similarity index 97%
rename from test/man/expect/test_package+ml/Include.3o
rename to test/generators/cases_pre408/man/Include.3o
index 4013eee3b9..e264520acc 100644
--- a/test/man/expect/test_package+ml/Include.3o
+++ b/test/generators/cases_pre408/man/Include.3o
@@ -1,7 +1,7 @@
.TH Include 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Include
+test\.Include
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Include2.3o b/test/generators/cases_pre408/man/Include2.3o
similarity index 96%
rename from test/man/expect/test_package+ml/Include2.3o
rename to test/generators/cases_pre408/man/Include2.3o
index 7a146a155f..6c7864c47f 100644
--- a/test/man/expect/test_package+ml/Include2.3o
+++ b/test/generators/cases_pre408/man/Include2.3o
@@ -1,7 +1,7 @@
.TH Include2 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Include2
+test\.Include2
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Include2.X.3o b/test/generators/cases_pre408/man/Include2.X.3o
new file mode 100644
index 0000000000..e6525c298e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Include2.X.3o
@@ -0,0 +1,17 @@
+
+.TH X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Include2\.X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Include2\.X\fR
+.in
+.sp
+.fi
+Comment about X that should not appear when including X below\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = int
diff --git a/test/generators/cases_pre408/man/Include2.Y.3o b/test/generators/cases_pre408/man/Include2.Y.3o
new file mode 100644
index 0000000000..70bd5990a2
--- /dev/null
+++ b/test/generators/cases_pre408/man/Include2.Y.3o
@@ -0,0 +1,17 @@
+
+.TH Y 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Include2\.Y
+.SH Synopsis
+.sp
+.in 2
+\fBModule Include2\.Y\fR
+.in
+.sp
+.fi
+Top-comment of Y\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Include2.Y_include_doc.3o b/test/generators/cases_pre408/man/Include2.Y_include_doc.3o
new file mode 100644
index 0000000000..cf5ff58313
--- /dev/null
+++ b/test/generators/cases_pre408/man/Include2.Y_include_doc.3o
@@ -0,0 +1,14 @@
+
+.TH Y_include_doc 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Include2\.Y_include_doc
+.SH Synopsis
+.sp
+.in 2
+\fBModule Include2\.Y_include_doc\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = Y\.t
diff --git a/test/generators/cases_pre408/man/Include2.Y_include_synopsis.3o b/test/generators/cases_pre408/man/Include2.Y_include_synopsis.3o
new file mode 100644
index 0000000000..6c51464290
--- /dev/null
+++ b/test/generators/cases_pre408/man/Include2.Y_include_synopsis.3o
@@ -0,0 +1,17 @@
+
+.TH Y_include_synopsis 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Include2\.Y_include_synopsis
+.SH Synopsis
+.sp
+.in 2
+\fBModule Include2\.Y_include_synopsis\fR
+.in
+.sp
+.fi
+The include Y below should have the synopsis from Y's top-comment attached to it\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = Y\.t
diff --git a/test/man/expect/test_package+ml/Include_sections.3o b/test/generators/cases_pre408/man/Include_sections.3o
similarity index 98%
rename from test/man/expect/test_package+ml/Include_sections.3o
rename to test/generators/cases_pre408/man/Include_sections.3o
index d5c2a51b2d..c45679f2e4 100644
--- a/test/man/expect/test_package+ml/Include_sections.3o
+++ b/test/generators/cases_pre408/man/Include_sections.3o
@@ -1,7 +1,7 @@
.TH Include_sections 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Include_sections
+test\.Include_sections
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Interlude.3o b/test/generators/cases_pre408/man/Interlude.3o
similarity index 96%
rename from test/man/expect/test_package+ml/Interlude.3o
rename to test/generators/cases_pre408/man/Interlude.3o
index 2cb1d14aa7..4818da7418 100644
--- a/test/man/expect/test_package+ml/Interlude.3o
+++ b/test/generators/cases_pre408/man/Interlude.3o
@@ -1,7 +1,7 @@
.TH Interlude 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Interlude
+test\.Interlude
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Markup.3o b/test/generators/cases_pre408/man/Markup.3o
similarity index 99%
rename from test/man/expect/test_package+ml/Markup.3o
rename to test/generators/cases_pre408/man/Markup.3o
index b1f56faa50..26a9679656 100644
--- a/test/man/expect/test_package+ml/Markup.3o
+++ b/test/generators/cases_pre408/man/Markup.3o
@@ -1,7 +1,7 @@
.TH Markup 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Markup
+test\.Markup
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Module.3o b/test/generators/cases_pre408/man/Module.3o
similarity index 99%
rename from test/man/expect/test_package+ml/Module.3o
rename to test/generators/cases_pre408/man/Module.3o
index a7da62d021..d2e3c611e9 100644
--- a/test/man/expect/test_package+ml/Module.3o
+++ b/test/generators/cases_pre408/man/Module.3o
@@ -1,7 +1,7 @@
.TH Module 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Module
+test\.Module
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Module.M'.3o b/test/generators/cases_pre408/man/Module.M'.3o
new file mode 100644
index 0000000000..b2cbc74554
--- /dev/null
+++ b/test/generators/cases_pre408/man/Module.M'.3o
@@ -0,0 +1,14 @@
+
+.TH M' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Module\.M'
+.SH Synopsis
+.sp
+.in 2
+\fBModule Module\.M'\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Module.Mutually.3o b/test/generators/cases_pre408/man/Module.Mutually.3o
new file mode 100644
index 0000000000..80ea717abf
--- /dev/null
+++ b/test/generators/cases_pre408/man/Module.Mutually.3o
@@ -0,0 +1,14 @@
+
+.TH Mutually 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Module\.Mutually
+.SH Synopsis
+.sp
+.in 2
+\fBModule Module\.Mutually\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Module.Recursive.3o b/test/generators/cases_pre408/man/Module.Recursive.3o
new file mode 100644
index 0000000000..c0dea99a88
--- /dev/null
+++ b/test/generators/cases_pre408/man/Module.Recursive.3o
@@ -0,0 +1,14 @@
+
+.TH Recursive 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Module\.Recursive
+.SH Synopsis
+.sp
+.in 2
+\fBModule Module\.Recursive\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/man/expect/test_package+ml/Nested.3o b/test/generators/cases_pre408/man/Nested.3o
similarity index 97%
rename from test/man/expect/test_package+ml/Nested.3o
rename to test/generators/cases_pre408/man/Nested.3o
index cfff6f1403..0a1a755366 100644
--- a/test/man/expect/test_package+ml/Nested.3o
+++ b/test/generators/cases_pre408/man/Nested.3o
@@ -1,7 +1,7 @@
.TH Nested 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Nested
+test\.Nested
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Nested.F.3o b/test/generators/cases_pre408/man/Nested.F.3o
similarity index 96%
rename from test/man/expect/test_package+ml/Nested.F.3o
rename to test/generators/cases_pre408/man/Nested.F.3o
index 4bf19ba437..3e8b37a584 100644
--- a/test/man/expect/test_package+ml/Nested.F.3o
+++ b/test/generators/cases_pre408/man/Nested.F.3o
@@ -1,7 +1,7 @@
.TH F 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Nested\.F
+test\.Nested\.F
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Nested.X.3o b/test/generators/cases_pre408/man/Nested.X.3o
similarity index 93%
rename from test/man/expect/test_package+ml/Nested.X.3o
rename to test/generators/cases_pre408/man/Nested.X.3o
index d9f6f77f4a..18dc675861 100644
--- a/test/man/expect/test_package+ml/Nested.X.3o
+++ b/test/generators/cases_pre408/man/Nested.X.3o
@@ -1,7 +1,7 @@
.TH X 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Nested\.X
+test\.Nested\.X
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Nested.inherits.3o b/test/generators/cases_pre408/man/Nested.inherits.3o
similarity index 82%
rename from test/man/expect/test_package+ml/Nested.inherits.3o
rename to test/generators/cases_pre408/man/Nested.inherits.3o
index 78176e0d46..ddadd2fda6 100644
--- a/test/man/expect/test_package+ml/Nested.inherits.3o
+++ b/test/generators/cases_pre408/man/Nested.inherits.3o
@@ -1,7 +1,7 @@
.TH inherits 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Nested\.inherits
+test\.Nested\.inherits
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Nested.z.3o b/test/generators/cases_pre408/man/Nested.z.3o
similarity index 94%
rename from test/man/expect/test_package+ml/Nested.z.3o
rename to test/generators/cases_pre408/man/Nested.z.3o
index f9cfa01601..2a269d7400 100644
--- a/test/man/expect/test_package+ml/Nested.z.3o
+++ b/test/generators/cases_pre408/man/Nested.z.3o
@@ -1,7 +1,7 @@
.TH z 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Nested\.z
+test\.Nested\.z
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Ocamlary.3o b/test/generators/cases_pre408/man/Ocamlary.3o
new file mode 100644
index 0000000000..d119e6802a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.3o
@@ -0,0 +1,1971 @@
+
+.TH Ocamlary 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\fR
+.in
+.sp
+.fi
+This is an \fIinterface\fR with \fBall\fR of the module system features\. This documentation demonstrates:
+.nf
+.sp
+.fi
+\(bu comment formatting
+.br
+\(bu unassociated comments
+.br
+\(bu documentation sections
+.br
+\(bu module system documentation including
+.sp
+.ti +2
+1) submodules
+.br
+.ti +2
+2) module aliases
+.br
+.ti +2
+3) module types
+.br
+.ti +2
+4) module type aliases
+.br
+.ti +2
+5) modules with signatures
+.br
+.ti +2
+6) modules with aliased signatures
+.nf
+.sp
+.fi
+A numbered list:
+.nf
+.sp
+.fi
+1) 3
+.br
+2) 2
+.br
+3) 1
+.nf
+.sp
+.fi
+David Sheets is the author\.
+.nf
+.sp
+.fi
+@author: David Sheets
+.nf
+.SH Documentation
+.sp
+.nf
+.fi
+You may find more information about this HTML documentation renderer at
+.UR https://github.com/dsheets/ocamlary
+github\.com/dsheets/ocamlary
+.UE
+\.
+.nf
+.sp
+.fi
+This is some verbatim text:
+.sp
+.EX
+verbatim
+.EE
+.nf
+.sp
+.fi
+This is some verbatim text:
+.sp
+.EX
+[][df[]]}}
+.EE
+.nf
+.sp
+.fi
+Here is some raw LaTeX:
+.nf
+.sp
+.fi
+Here is an index table of Empty modules:
+.sp
+@\f[CI]Empty\fR: A plain, empty module
+.br
+@\f[CI]EmptyAlias\fR: A plain module alias of Empty
+.nf
+.sp
+.fi
+Here is a table of links to indexes: indexlist
+.nf
+.sp
+.fi
+Here is some superscript: x2
+.nf
+.sp
+.fi
+Here is some subscript: x0
+.nf
+.sp
+.fi
+Here are some escaped brackets: { [ @ ] }
+.nf
+.sp
+.fi
+Here is some emphasis followed by code\.
+.nf
+.sp
+.fi
+An unassociated comment
+.nf
+.sp
+.in 3
+\fB1 Level 1\fR
+.in
+.sp
+.in 4
+\fB1\.1 Level 2\fR
+.in
+.sp
+.in 5
+\fB1\.1\.1 Level 3\fR
+.in
+.sp
+.in 6
+\fBLevel 4\fR
+.in
+.sp
+.in 5
+\fB1\.1\.2 Basic module stuff\fR
+.in
+.sp
+\f[CB]module\fR Empty : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+A plain, empty module
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR Empty = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+An ambiguous, misnamed module type
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR MissingComment = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+An ambiguous, misnamed module type
+.nf
+.sp
+.in 3
+\fB2 Section 9000\fR
+.in
+.sp
+\f[CB]module\fR EmptyAlias = Empty
+.fi
+.br
+.ti +2
+A plain module alias of Empty
+.nf
+.sp
+.in 5
+\fB2\.1\.1 EmptySig\fR
+.in
+.sp
+\f[CB]module\fR \f[CB]type\fR EmptySig = \f[CB]sig\fR \f[CB]end\fR
+.fi
+.br
+.ti +2
+A plain, empty module signature
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR EmptySigAlias = \f[CB]sig\fR \f[CB]end\fR
+.fi
+.br
+.ti +2
+A plain, empty module signature alias of
+.nf
+.sp
+\f[CB]module\fR ModuleWithSignature : EmptySig
+.fi
+.br
+.ti +2
+A plain module of a signature of \f[CI]EmptySig\fR (reference)
+.nf
+.sp
+\f[CB]module\fR ModuleWithSignatureAlias : EmptySigAlias
+.fi
+.br
+.ti +2
+A plain module with an alias signature
+.nf
+.sp
+\f[CB]module\fR One : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR SigForMod = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR Inner : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR Empty = \f[CB]sig\fR \f[CB]end\fR
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+There's a signature in a module in this signature\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR SuperSig = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR SubSigA = \f[CB]sig\fR
+.br
+.ti +4
+.sp
+.ti +4
+\fBA Labeled Section Header Inside of a Signature\fR
+.sp
+.ti +4
+\f[CB]type\fR t
+.sp
+.ti +4
+\f[CB]module\fR SubSigAMod : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR sub_sig_a_mod
+.br
+.ti +4
+\f[CB]end\fR
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR SubSigB = \f[CB]sig\fR
+.br
+.ti +4
+.sp
+.ti +4
+\fBAnother Labeled Section Header Inside of a Signature\fR
+.sp
+.ti +4
+\f[CB]type\fR t
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR EmptySig = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR not_actually_empty
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR One = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR two
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR SuperSig = \f[CB]sig\fR \f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+.fi
+For a good time, see SuperSig\.SubSigA\.subSig or SuperSig\.SubSigB\.subSig or \f[CI]SuperSig\.EmptySig\fR\. Section \f[CI]Section 9000\fR is also interesting\. \f[CI]EmptySig\fR is the section and \f[CI]EmptySig\fR is the module signature\.
+.nf
+.sp
+\f[CB]module\fR Buffer : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Buffer\.t
+.nf
+.sp
+.fi
+Some text before exception title\.
+.nf
+.sp
+.in 5
+\fB2\.1\.2 Basic exception stuff\fR
+.in
+.sp
+.fi
+After exception title\.
+.nf
+.sp
+\f[CB]exception\fR \f[CB]Kaboom\fR \f[CB]of\fR unit
+.fi
+.br
+.ti +2
+Unary exception constructor
+.nf
+.sp
+\f[CB]exception\fR \f[CB]Kablam\fR \f[CB]of\fR unit * unit
+.fi
+.br
+.ti +2
+Binary exception constructor
+.nf
+.sp
+\f[CB]exception\fR \f[CB]Kapow\fR \f[CB]of\fR unit * unit
+.fi
+.br
+.ti +2
+Unary exception constructor over binary tuple
+.nf
+.sp
+\f[CB]exception\fR \f[CB]EmptySig\fR
+.fi
+.br
+.ti +2
+\f[CI]EmptySig\fR is a module and \f[CI]EmptySig\fR is this exception\.
+.nf
+.sp
+\f[CB]exception\fR \f[CB]EmptySigAlias\fR
+.fi
+.br
+.ti +2
+\f[CI]EmptySigAlias\fR is this exception\.
+.nf
+.sp
+.in 5
+\fB2\.1\.3 Basic type and value stuff with advanced doc comments\fR
+.in
+.sp
+\f[CB]type\fR ('a, 'b) a_function = \f[CB]'a\fR \f[CB]\->\fR \f[CB]'b\fR
+.fi
+.br
+.ti +2
+\f[CI]a_function\fR is this type and \f[CI]a_function\fR is the value below\.
+.nf
+.sp
+\f[CB]val\fR a_function : x:int \f[CB]\->\fR int
+.fi
+.br
+.ti +2
+This is a_function with param and return type\.
+.sp
+.ti +2
+@parameter x: the x coordinate
+.br
+.ti +2
+@returns: the y coordinate
+.nf
+.sp
+\f[CB]val\fR fun_fun_fun : ((int, int) a_function, (unit, unit) a_function) a_function
+.sp
+\f[CB]val\fR fun_maybe : ?yes:unit \f[CB]\->\fR unit \f[CB]\->\fR int
+.sp
+\f[CB]val\fR not_found : unit \f[CB]\->\fR unit
+.fi
+.br
+.ti +2
+@raises Not_found: That's all it does
+.nf
+.sp
+\f[CB]val\fR ocaml_org : string
+.fi
+.br
+.ti +2
+@see
+.UR http://ocaml.org/
+http://ocaml\.org/
+.UE
+: The OCaml Web site
+.nf
+.sp
+\f[CB]val\fR some_file : string
+.fi
+.br
+.ti +2
+@see some_file: The file called some_file
+.nf
+.sp
+\f[CB]val\fR some_doc : string
+.fi
+.br
+.ti +2
+@see some_doc: The document called some_doc
+.nf
+.sp
+\f[CB]val\fR since_mesozoic : unit
+.fi
+.br
+.ti +2
+This value was introduced in the Mesozoic era\.
+.sp
+.ti +2
+@since: mesozoic
+.nf
+.sp
+\f[CB]val\fR changing : unit
+.fi
+.br
+.ti +2
+This value has had changes in 1\.0\.0, 1\.1\.0, and 1\.2\.0\.
+.sp
+.ti +2
+@before 1\.0\.0: before 1\.0\.0
+.br
+.ti +2
+@before 1\.1\.0: before 1\.1\.0
+.br
+.ti +2
+@version: 1\.2\.0
+.nf
+.sp
+.in 5
+\fB2\.1\.4 Some Operators\fR
+.in
+.sp
+\f[CB]val\fR (~-) : unit
+.sp
+\f[CB]val\fR (!) : unit
+.sp
+\f[CB]val\fR (@) : unit
+.sp
+\f[CB]val\fR ($) : unit
+.sp
+\f[CB]val\fR (%) : unit
+.sp
+\f[CB]val\fR (&) : unit
+.sp
+\f[CB]val\fR (*) : unit
+.sp
+\f[CB]val\fR (-) : unit
+.sp
+\f[CB]val\fR (+) : unit
+.sp
+\f[CB]val\fR (-?) : unit
+.sp
+\f[CB]val\fR (/) : unit
+.sp
+\f[CB]val\fR (:=) : unit
+.sp
+\f[CB]val\fR (=) : unit
+.sp
+\f[CB]val\fR (land) : unit
+.sp
+.in 5
+\fB2\.1\.5 Advanced Module Stuff\fR
+.in
+.sp
+\f[CB]module\fR CollectionModule : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for CollectionModule\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR COLLECTION = \f[CB]sig\fR
+.br
+.ti +2
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +2
+\f[CB]type\fR collection
+.fi
+.br
+.ti +4
+This comment is for collection\.
+.nf
+.sp
+.ti +2
+\f[CB]type\fR element
+.sp
+.ti +2
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+module type of
+.nf
+.sp
+\f[CB]module\fR Recollection (C : COLLECTION) : COLLECTION \f[CB]with\fR \f[CB]type\fR collection = C\.element list \f[CB]and\fR \f[CB]type\fR element = C\.collection
+.sp
+\f[CB]module\fR \f[CB]type\fR MMM = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR C : \f[CB]sig\fR
+.br
+.ti +4
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR collection
+.fi
+.br
+.ti +6
+This comment is for collection\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR element
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR RECOLLECTION = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR C = Recollection(CollectionModule)
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR RecollectionModule = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR collection = CollectionModule\.element list
+.sp
+.ti +2
+\f[CB]type\fR element = CollectionModule\.collection
+.sp
+.ti +2
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR A = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.sp
+.ti +2
+\f[CB]module\fR Q : \f[CB]sig\fR
+.br
+.ti +4
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR collection
+.fi
+.br
+.ti +6
+This comment is for collection\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR element
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR B = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.sp
+.ti +2
+\f[CB]module\fR Q : \f[CB]sig\fR
+.br
+.ti +4
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR collection
+.fi
+.br
+.ti +6
+This comment is for collection\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR element
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR C = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.sp
+.ti +2
+\f[CB]module\fR Q : \f[CB]sig\fR
+.br
+.ti +4
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR collection
+.fi
+.br
+.ti +6
+This comment is for collection\.
+.nf
+.sp
+.ti +4
+\f[CB]type\fR element
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +6
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +8
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +10
+This comment is for t\.
+.nf
+
+.br
+.ti +6
+\f[CB]end\fR
+.fi
+.br
+.ti +8
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+This module type includes two signatures\.
+.nf
+.sp
+\f[CB]module\fR FunctorTypeOf (Collection : \f[CB]module\fR \f[CB]type\fR \f[CB]of\fR CollectionModule) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for FunctorTypeOf\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR IncludeModuleType = \f[CB]sig\fR
+.br
+.ti +2
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for IncludeModuleType\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR ToInclude = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR IncludedA : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR IncludedB = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR s
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR IncludedA : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR IncludedB = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR s
+.br
+\f[CB]end\fR
+.sp
+.in 5
+\fB2\.1\.6 Advanced Type Stuff\fR
+.in
+.sp
+\f[CB]type\fR record = {
+.br
+.ti +2
+field1 : int;
+.br
+.ti +4
+(* This comment is for field1\. *)
+.br
+.ti +2
+field2 : int;
+.br
+.ti +4
+(* This comment is for field2\. *)
+.br
+}
+.fi
+.br
+.ti +2
+This comment is for record\.
+.sp
+.ti +2
+This comment is also for record\.
+.nf
+.sp
+\f[CB]type\fR mutable_record = {
+.br
+.ti +2
+\f[CB]mutable\fR a : int;
+.br
+.ti +4
+(* a is first and mutable *)
+.br
+.ti +2
+b : unit;
+.br
+.ti +4
+(* b is second and immutable *)
+.br
+.ti +2
+\f[CB]mutable\fR c : int;
+.br
+.ti +4
+(* c is third and mutable *)
+.br
+}
+.sp
+\f[CB]type\fR universe_record = {
+.br
+.ti +2
+nihilate : a\. \f[CB]'a\fR \f[CB]\->\fR unit;
+.br
+}
+.sp
+\f[CB]type\fR variant =
+.br
+.ti +2
+| \f[CB]TagA\fR
+.br
+.ti +4
+(* This comment is for TagA\. *)
+.br
+.ti +2
+| \f[CB]ConstrB\fR \f[CB]of\fR int
+.br
+.ti +4
+(* This comment is for ConstrB\. *)
+.br
+.ti +2
+| \f[CB]ConstrC\fR \f[CB]of\fR int * int
+.br
+.ti +4
+(* This comment is for binary ConstrC\. *)
+.br
+.ti +2
+| \f[CB]ConstrD\fR \f[CB]of\fR int * int
+.br
+.ti +4
+(* This comment is for unary ConstrD of binary tuple\. *)
+.br
+.fi
+.br
+.ti +2
+This comment is for variant\.
+.sp
+.ti +2
+This comment is also for variant\.
+.nf
+.sp
+\f[CB]type\fR poly_variant = [
+.br
+.ti +2
+| `TagA
+.br
+.ti +2
+| `ConstrB \f[CB]of\fR int
+.br
+ ]
+.fi
+.br
+.ti +2
+This comment is for poly_variant\.
+.sp
+.ti +2
+Wow! It was a polymorphic variant!
+.nf
+.sp
+\f[CB]type\fR (_, _) full_gadt =
+.br
+.ti +2
+| \f[CB]Tag\fR : (unit, unit) full_gadt
+.br
+.ti +2
+| \f[CB]First\fR : \f[CB]'a\fR \f[CB]\->\fR (\f[CB]'a\fR, unit) full_gadt
+.br
+.ti +2
+| \f[CB]Second\fR : \f[CB]'a\fR \f[CB]\->\fR (unit, \f[CB]'a\fR) full_gadt
+.br
+.ti +2
+| \f[CB]Exist\fR : \f[CB]'a\fR * \f[CB]'b\fR \f[CB]\->\fR (\f[CB]'b\fR, unit) full_gadt
+.br
+.fi
+.br
+.ti +2
+This comment is for full_gadt\.
+.sp
+.ti +2
+Wow! It was a GADT!
+.nf
+.sp
+\f[CB]type\fR 'a partial_gadt =
+.br
+.ti +2
+| \f[CB]AscribeTag\fR : \f[CB]'a\fR partial_gadt
+.br
+.ti +2
+| \f[CB]OfTag\fR \f[CB]of\fR \f[CB]'a\fR partial_gadt
+.br
+.ti +2
+| \f[CB]ExistGadtTag\fR : (\f[CB]'a\fR \f[CB]\->\fR \f[CB]'b\fR) \f[CB]\->\fR \f[CB]'a\fR partial_gadt
+.br
+.fi
+.br
+.ti +2
+This comment is for partial_gadt\.
+.sp
+.ti +2
+Wow! It was a mixed GADT!
+.nf
+.sp
+\f[CB]type\fR alias = variant
+.fi
+.br
+.ti +2
+This comment is for alias\.
+.nf
+.sp
+\f[CB]type\fR tuple = (alias * alias) * alias * (alias * alias)
+.fi
+.br
+.ti +2
+This comment is for tuple\.
+.nf
+.sp
+\f[CB]type\fR variant_alias = variant =
+.br
+.ti +2
+| \f[CB]TagA\fR
+.br
+.ti +2
+| \f[CB]ConstrB\fR \f[CB]of\fR int
+.br
+.ti +2
+| \f[CB]ConstrC\fR \f[CB]of\fR int * int
+.br
+.ti +2
+| \f[CB]ConstrD\fR \f[CB]of\fR int * int
+.br
+.fi
+.br
+.ti +2
+This comment is for variant_alias\.
+.nf
+.sp
+\f[CB]type\fR record_alias = record = {
+.br
+.ti +2
+field1 : int;
+.br
+.ti +2
+field2 : int;
+.br
+}
+.fi
+.br
+.ti +2
+This comment is for record_alias\.
+.nf
+.sp
+\f[CB]type\fR poly_variant_union = [
+.br
+.ti +2
+| poly_variant
+.br
+.ti +2
+| `TagC
+.br
+ ]
+.fi
+.br
+.ti +2
+This comment is for poly_variant_union\.
+.nf
+.sp
+\f[CB]type\fR 'a poly_poly_variant = [
+.br
+.ti +2
+| `TagA \f[CB]of\fR \f[CB]'a\fR
+.br
+ ]
+.sp
+\f[CB]type\fR ('a, 'b) bin_poly_poly_variant = [
+.br
+.ti +2
+| `TagA \f[CB]of\fR \f[CB]'a\fR
+.br
+.ti +2
+| `ConstrB \f[CB]of\fR \f[CB]'b\fR
+.br
+ ]
+.sp
+\f[CB]type\fR 'a open_poly_variant = [> `TagA ] \f[CB]as\fR 'a
+.sp
+\f[CB]type\fR 'a open_poly_variant2 = [> `ConstrB of int ] \f[CB]as\fR 'a
+.sp
+\f[CB]type\fR 'a open_poly_variant_alias = \f[CB]'a\fR open_poly_variant open_poly_variant2
+.sp
+\f[CB]type\fR 'a poly_fun = [> `ConstrB of int ] \f[CB]as\fR 'a \f[CB]\->\fR \f[CB]'a\fR
+.sp
+\f[CB]type\fR 'a poly_fun_constraint = \f[CB]'a\fR \f[CB]\->\fR \f[CB]'a\fR \f[CB]constraint\fR \f[CB]'a\fR = [> `TagA ]
+.sp
+\f[CB]type\fR 'a closed_poly_variant = [< `One | `Two ] \f[CB]as\fR 'a
+.sp
+\f[CB]type\fR 'a clopen_poly_variant = [< `One | `Two of int | `Three Two Three ] \f[CB]as\fR 'a
+.sp
+\f[CB]type\fR nested_poly_variant = [
+.br
+.ti +2
+| `A
+.br
+.ti +2
+| `B \f[CB]of\fR [ `B1 | `B2 ]
+.br
+.ti +2
+| `C
+.br
+.ti +2
+| `D \f[CB]of\fR [ `D1 of [ `D1a ] ]
+.br
+ ]
+.sp
+\f[CB]type\fR ('a, 'b) full_gadt_alias = (\f[CB]'a\fR, \f[CB]'b\fR) full_gadt =
+.br
+.ti +2
+| \f[CB]Tag\fR : (unit, unit) full_gadt_alias
+.br
+.ti +2
+| \f[CB]First\fR : \f[CB]'a\fR \f[CB]\->\fR (\f[CB]'a\fR, unit) full_gadt_alias
+.br
+.ti +2
+| \f[CB]Second\fR : \f[CB]'a\fR \f[CB]\->\fR (unit, \f[CB]'a\fR) full_gadt_alias
+.br
+.ti +2
+| \f[CB]Exist\fR : \f[CB]'a\fR * \f[CB]'b\fR \f[CB]\->\fR (\f[CB]'b\fR, unit) full_gadt_alias
+.br
+.fi
+.br
+.ti +2
+This comment is for full_gadt_alias\.
+.nf
+.sp
+\f[CB]type\fR 'a partial_gadt_alias = \f[CB]'a\fR partial_gadt =
+.br
+.ti +2
+| \f[CB]AscribeTag\fR : \f[CB]'a\fR partial_gadt_alias
+.br
+.ti +2
+| \f[CB]OfTag\fR \f[CB]of\fR \f[CB]'a\fR partial_gadt_alias
+.br
+.ti +2
+| \f[CB]ExistGadtTag\fR : (\f[CB]'a\fR \f[CB]\->\fR \f[CB]'b\fR) \f[CB]\->\fR \f[CB]'a\fR partial_gadt_alias
+.br
+.fi
+.br
+.ti +2
+This comment is for partial_gadt_alias\.
+.nf
+.sp
+\f[CB]exception\fR \f[CB]Exn_arrow\fR : unit \f[CB]\->\fR exn
+.fi
+.br
+.ti +2
+This comment is for \f[CI]Exn_arrow\fR\.
+.nf
+.sp
+\f[CB]type\fR mutual_constr_a =
+.br
+.ti +2
+| \f[CB]A\fR
+.br
+.ti +2
+| \f[CB]B_ish\fR \f[CB]of\fR mutual_constr_b
+.br
+.ti +4
+(* This comment is between \f[CI]mutual_constr_a\fR and \f[CI]mutual_constr_b\fR\. *)
+.br
+.fi
+.br
+.ti +2
+This comment is for \f[CI]mutual_constr_a\fR then \f[CI]mutual_constr_b\fR\.
+.nf
+.sp
+\f[CB]and\fR mutual_constr_b =
+.br
+.ti +2
+| \f[CB]B\fR
+.br
+.ti +2
+| \f[CB]A_ish\fR \f[CB]of\fR mutual_constr_a
+.br
+.ti +4
+(* This comment must be here for the next to associate correctly\. *)
+.br
+.fi
+.br
+.ti +2
+This comment is for \f[CI]mutual_constr_b\fR then \f[CI]mutual_constr_a\fR\.
+.nf
+.sp
+\f[CB]type\fR rec_obj = < f : int; g : unit \f[CB]\->\fR unit; h : rec_obj; >
+.sp
+\f[CB]type\fR 'a open_obj = < f : int; g : unit \f[CB]\->\fR unit; \.\. > \f[CB]as\fR 'a
+.sp
+\f[CB]type\fR 'a oof = < a : unit; \.\. > \f[CB]as\fR 'a \f[CB]\->\fR \f[CB]'a\fR
+.sp
+\f[CB]type\fR 'a any_obj = < \.\. > \f[CB]as\fR 'a
+.sp
+\f[CB]type\fR empty_obj = < >
+.sp
+\f[CB]type\fR one_meth = < meth : unit; >
+.sp
+\f[CB]type\fR ext = \.\.
+.fi
+.br
+.ti +2
+A mystery wrapped in an ellipsis
+.nf
+.sp
+\f[CB]type\fR ext +=
+.br
+.ti +2
+| \f[CB]ExtA\fR
+.br
+.sp
+\f[CB]type\fR ext +=
+.br
+.ti +2
+| \f[CB]ExtB\fR
+.br
+.sp
+\f[CB]type\fR ext +=
+.br
+.ti +2
+| \f[CB]ExtC\fR \f[CB]of\fR unit
+.br
+.ti +2
+| \f[CB]ExtD\fR \f[CB]of\fR ext
+.br
+.sp
+\f[CB]type\fR ext +=
+.br
+.ti +2
+| \f[CB]ExtE\fR
+.br
+.sp
+\f[CB]type\fR ext +=
+.br
+.ti +2
+| \f[CB]ExtF\fR
+.br
+.sp
+\f[CB]type\fR 'a poly_ext = \.\.
+.fi
+.br
+.ti +2
+'a poly_ext
+.nf
+.sp
+\f[CB]type\fR poly_ext +=
+.br
+.ti +2
+| \f[CB]Foo\fR \f[CB]of\fR \f[CB]'b\fR
+.br
+.ti +2
+| \f[CB]Bar\fR \f[CB]of\fR \f[CB]'b\fR * \f[CB]'b\fR
+.br
+.ti +4
+(* 'b poly_ext *)
+.br
+.sp
+\f[CB]type\fR poly_ext +=
+.br
+.ti +2
+| \f[CB]Quux\fR \f[CB]of\fR \f[CB]'c\fR
+.br
+.ti +4
+(* 'c poly_ext *)
+.br
+.sp
+\f[CB]module\fR ExtMod : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR ExtMod\.t +=
+.br
+.ti +2
+| \f[CB]ZzzTop0\fR
+.br
+.ti +4
+(* It's got the rock *)
+.br
+.sp
+\f[CB]type\fR ExtMod\.t +=
+.br
+.ti +2
+| \f[CB]ZzzTop\fR \f[CB]of\fR unit
+.br
+.ti +4
+(* and it packs a unit\. *)
+.br
+.sp
+\f[CB]val\fR launch_missiles : unit \f[CB]\->\fR unit
+.fi
+.br
+.ti +2
+Rotate keys on my mark\.\.\.
+.nf
+.sp
+\f[CB]type\fR my_mod = (\f[CB]module\fR COLLECTION)
+.fi
+.br
+.ti +2
+A brown paper package tied up with string
+.nf
+.sp
+\f[CB]class\fR empty_class : \f[CB]object\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]class\fR one_method_class : \f[CB]object\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]class\fR two_method_class : \f[CB]object\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]class\fR 'a param_class : \f[CB]'a\fR \f[CB]\->\fR \f[CB]object\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR my_unit_object = unit param_class
+.sp
+\f[CB]type\fR 'a my_unit_class = unit param_class \f[CB]as\fR 'a
+.sp
+\f[CB]module\fR Dep1 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep2 (Arg : \f[CB]sig\fR \.\.\. \f[CB]end\fR) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR dep1 = Dep2(Dep1)\.B\.c
+.sp
+\f[CB]module\fR Dep3 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep4 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep5 (Arg : \f[CB]sig\fR \.\.\. \f[CB]end\fR) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR dep2 = Dep5(Dep4)\.Z\.X\.b
+.sp
+\f[CB]type\fR dep3 = Dep5(Dep4)\.Z\.Y\.a
+.sp
+\f[CB]module\fR Dep6 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep7 (Arg : \f[CB]sig\fR \.\.\. \f[CB]end\fR) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR dep4 = Dep7(Dep6)\.M\.Y\.d
+.sp
+\f[CB]module\fR Dep8 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep9 (X : \f[CB]sig\fR \.\.\. \f[CB]end\fR) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR Dep10 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t = int
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR Dep11 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep12 (Arg : \f[CB]sig\fR \.\.\. \f[CB]end\fR) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Dep13 : Dep12(Dep11)\.T
+.sp
+\f[CB]type\fR dep5 = Dep13\.c
+.sp
+\f[CB]module\fR \f[CB]type\fR With1 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR M : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR S
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR N : M\.S
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR With2 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR With3 : With1 \f[CB]with\fR \f[CB]module\fR M = With2
+.sp
+\f[CB]type\fR with1 = With3\.N\.t
+.sp
+\f[CB]module\fR With4 : With1 \f[CB]with\fR \f[CB]module\fR M := With2
+.sp
+\f[CB]type\fR with2 = With4\.N\.t
+.sp
+\f[CB]module\fR With5 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR With6 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR With7 (X : \f[CB]sig\fR \.\.\. \f[CB]end\fR) : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR With8 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR M : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t
+.br
+.ti +4
+\f[CB]end\fR
+.sp
+.ti +4
+\f[CB]module\fR N : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = With5\.N\.t
+.br
+.ti +4
+\f[CB]end\fR
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR With9 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR With10 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR With11 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR M = With9
+.sp
+.ti +2
+\f[CB]module\fR N : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = int
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR NestedInclude1 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR NestedInclude2 = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR nested_include
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR NestedInclude2 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR nested_include
+.br
+\f[CB]end\fR
+.sp
+\f[CB]type\fR nested_include = int
+.sp
+\f[CB]module\fR DoubleInclude1 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR DoubleInclude3 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR double_include
+.sp
+\f[CB]module\fR IncludeInclude1 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR IncludeInclude2 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR include_include
+.br
+\f[CB]end\fR
+.sp
+\f[CB]type\fR include_include
+.sp
+.in 3
+\fB3 Trying the {!modules: \.\.\.} command\.\fR
+.in
+.sp
+.fi
+With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references\.
+.sp
+With odoc, everything should be resolved (and linked) but only toplevel units will be documented\.
+.sp
+@\f[CI]Dep1\.X\fR:
+.br
+@DocOckTypes:
+.br
+@\f[CI]Ocamlary\.IncludeInclude1\fR:
+.br
+@\f[CI]Ocamlary\fR: This is an \fIinterface\fR with \fBall\fR of the module system features\. This documentation demonstrates:
+.nf
+.sp
+.in 5
+\fB3\.1\.1 Weirder usages involving module types\fR
+.in
+.sp
+.fi
+@IncludeInclude1\.IncludeInclude2:
+.br
+@Dep4\.T:
+.br
+@\f[CI]A\.Q\fR:
+.nf
+.sp
+.in 3
+\fB4 Playing with @canonical paths\fR
+.in
+.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
+.in 3
+\fB5 Aliases again\fR
+.in
+.sp
+\f[CB]module\fR Aliases : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Let's imitate jst's layout\.
+.nf
+.sp
+.in 3
+\fB6 Section title splicing\fR
+.in
+.sp
+.fi
+I can refer to
+.sp
+\(bu {!section:indexmodules} : \f[CI]Trying the {!modules: \.\.\.} command\.\fR
+.br
+\(bu {!aliases} : \f[CI]Aliases again\fR
+.sp
+But also to things in submodules:
+.sp
+\(bu {!section:SuperSig\.SubSigA\.subSig} : SuperSig\.SubSigA\.subSig
+.br
+\(bu {!Aliases\.incl} : \f[CI]Aliases:incl\fR
+.sp
+And just to make sure we do not mess up:
+.sp
+\(bu {{!section:indexmodules}A} : \f[CI]A\fR
+.br
+\(bu {{!aliases}B} : \f[CI]B\fR
+.br
+\(bu {{!section:SuperSig\.SubSigA\.subSig}C} : \f[CI]C\fR
+.br
+\(bu {{!Aliases\.incl}D} : \f[CI]D\fR
+.nf
+.sp
+.in 3
+\fB7 New reference syntax\fR
+.in
+.sp
+\f[CB]module\fR \f[CB]type\fR M = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR M : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+.fi
+Here goes:
+.sp
+\(bu {!module-M\.t} : \f[CI]M\.t\fR
+.br
+\(bu {!module-type-M\.t} : \f[CI]M\.t\fR
+.nf
+.sp
+\f[CB]module\fR Only_a_module : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+.fi
+Some here should fail:
+.sp
+\(bu {!Only_a_module\.t} : \f[CI]Only_a_module\.t\fR
+.br
+\(bu {!module-Only_a_module\.t} : \f[CI]Only_a_module\.t\fR
+.br
+\(bu {!module-type-Only_a_module\.t} : Only_a_module\.t : \f[CI]test\fR
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR TypeExt = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t = \.\.
+.sp
+.ti +2
+\f[CB]type\fR t +=
+.br
+.ti +4
+| \f[CB]C\fR
+.br
+.ti +2
+.sp
+.ti +2
+\f[CB]val\fR f : t \f[CB]\->\fR unit
+.br
+\f[CB]end\fR
+.sp
+\f[CB]type\fR new_t = \.\.
+.sp
+\f[CB]type\fR new_t +=
+.br
+.ti +2
+| \f[CB]C\fR
+.br
+.sp
+\f[CB]module\fR \f[CB]type\fR TypeExtPruned = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR new_t +=
+.br
+.ti +4
+| \f[CB]C\fR
+.br
+.ti +2
+.sp
+.ti +2
+\f[CB]val\fR f : new_t \f[CB]\->\fR unit
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.3o
new file mode 100644
index 0000000000..3eaedb9e52
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.3o
@@ -0,0 +1,81 @@
+
+.TH Aliases 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Aliases\fR
+.in
+.sp
+.fi
+Let's imitate jst's layout\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Foo__A : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Foo__B : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Foo__C : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Foo__D : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Foo__E : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Foo__ : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Foo : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR A' = Foo\.A
+.sp
+\f[CB]type\fR tata = Foo\.A\.t
+.sp
+\f[CB]type\fR tbtb = Foo\.B\.t
+.sp
+\f[CB]type\fR tete
+.sp
+\f[CB]type\fR tata' = A'\.t
+.sp
+\f[CB]type\fR tete2 = Foo\.E\.t
+.sp
+\f[CB]module\fR Std : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR stde = Std\.E\.t
+.sp
+.in 5
+\fB1\.1\.1 include of Foo\fR
+.in
+.sp
+.fi
+Just for giggle, let's see what happens when we include \f[CI]Foo\fR\.
+.nf
+.sp
+\f[CB]module\fR A = Foo\.A
+.sp
+\f[CB]module\fR B = Foo\.B
+.sp
+\f[CB]module\fR C = Foo\.C
+.sp
+\f[CB]module\fR D = Foo\.D
+.sp
+\f[CB]module\fR E : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR testa = A\.t
+.sp
+.fi
+And also, let's refer to \f[CI]A\.t\fR and \f[CI]Foo\.B\.id\fR
+.nf
+.sp
+\f[CB]module\fR P1 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR P2 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR X1 = P2\.Z
+.sp
+\f[CB]module\fR X2 = P2\.Z
+.sp
+\f[CB]type\fR p1 = X1\.t
+.sp
+\f[CB]type\fR p2 = X2\.t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.E.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.E.3o
new file mode 100644
index 0000000000..b9cfcad106
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.E.3o
@@ -0,0 +1,16 @@
+
+.TH E 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.E
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.E\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.3o
new file mode 100644
index 0000000000..4d9001ee8d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.3o
@@ -0,0 +1,22 @@
+
+.TH Foo 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR A : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR B : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR C : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR D : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR E : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.A.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.A.3o
new file mode 100644
index 0000000000..ed7832fadc
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.A.3o
@@ -0,0 +1,16 @@
+
+.TH A 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo\.A
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.A\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.B.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.B.3o
new file mode 100644
index 0000000000..c90edb7a5e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.B.3o
@@ -0,0 +1,16 @@
+
+.TH B 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo\.B
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.B\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.C.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.C.3o
new file mode 100644
index 0000000000..a686387000
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.C.3o
@@ -0,0 +1,16 @@
+
+.TH C 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo\.C
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.C\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.D.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.D.3o
new file mode 100644
index 0000000000..fc996a6a86
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.D.3o
@@ -0,0 +1,16 @@
+
+.TH D 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo\.D
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.D\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.E.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.E.3o
new file mode 100644
index 0000000000..104ecae2da
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo.E.3o
@@ -0,0 +1,16 @@
+
+.TH E 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo\.E
+.SH Synopsis
+.sp
+.in 2
+\fBModule Foo\.E\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__.3o
new file mode 100644
index 0000000000..bcedb038c2
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__.3o
@@ -0,0 +1,22 @@
+
+.TH Foo__ 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo__
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo__\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR A = Foo__A
+.sp
+\f[CB]module\fR B = Foo__B
+.sp
+\f[CB]module\fR C = Foo__C
+.sp
+\f[CB]module\fR D = Foo__D
+.sp
+\f[CB]module\fR E = Foo__E
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__A.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__A.3o
new file mode 100644
index 0000000000..b14b64b459
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__A.3o
@@ -0,0 +1,16 @@
+
+.TH Foo__A 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo__A
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo__A\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__B.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__B.3o
new file mode 100644
index 0000000000..5d5cb4b261
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__B.3o
@@ -0,0 +1,16 @@
+
+.TH Foo__B 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo__B
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo__B\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__C.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__C.3o
new file mode 100644
index 0000000000..ca7ea8f8df
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__C.3o
@@ -0,0 +1,16 @@
+
+.TH Foo__C 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo__C
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo__C\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__D.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__D.3o
new file mode 100644
index 0000000000..b38ec18d66
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__D.3o
@@ -0,0 +1,16 @@
+
+.TH Foo__D 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo__D
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo__D\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__E.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__E.3o
new file mode 100644
index 0000000000..904f378b75
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Foo__E.3o
@@ -0,0 +1,16 @@
+
+.TH Foo__E 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Foo__E
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Foo__E\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.P1.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.P1.3o
new file mode 100644
index 0000000000..61c0d7d029
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.P1.3o
@@ -0,0 +1,14 @@
+
+.TH P1 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.P1
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.P1\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Y : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.P1.Y.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.P1.Y.3o
new file mode 100644
index 0000000000..9c79d3f25d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.P1.Y.3o
@@ -0,0 +1,16 @@
+
+.TH Y 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.P1\.Y
+.SH Synopsis
+.sp
+.in 2
+\fBModule P1\.Y\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.P2.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.P2.3o
new file mode 100644
index 0000000000..9abf175a84
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.P2.3o
@@ -0,0 +1,14 @@
+
+.TH P2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.P2
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.P2\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Z = Z
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.P2.Z.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.P2.Z.3o
new file mode 100644
index 0000000000..bf97e9a90d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.P2.Z.3o
@@ -0,0 +1,19 @@
+
+.TH Z 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.P2\.Z
+.SH Synopsis
+.sp
+.in 2
+\fBModule P2\.Z\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.fi
+.nf
+.sp
+\f[CB]type\fR t
+.sp
+\f[CB]val\fR id : t \f[CB]\->\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Aliases.Std.3o b/test/generators/cases_pre408/man/Ocamlary.Aliases.Std.3o
new file mode 100644
index 0000000000..7c5ea28ef2
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Aliases.Std.3o
@@ -0,0 +1,22 @@
+
+.TH Std 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Aliases\.Std
+.SH Synopsis
+.sp
+.in 2
+\fBModule Aliases\.Std\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR A = Foo\.A
+.sp
+\f[CB]module\fR B = Foo\.B
+.sp
+\f[CB]module\fR C = Foo\.C
+.sp
+\f[CB]module\fR D = Foo\.D
+.sp
+\f[CB]module\fR E = Foo\.E
diff --git a/test/generators/cases_pre408/man/Ocamlary.Buffer.3o b/test/generators/cases_pre408/man/Ocamlary.Buffer.3o
new file mode 100644
index 0000000000..f64e89d3cd
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Buffer.3o
@@ -0,0 +1,17 @@
+
+.TH Buffer 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Buffer
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Buffer\fR
+.in
+.sp
+.fi
+Buffer\.t
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]val\fR f : Stdlib\.Buffer\.t \f[CB]\->\fR unit
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.3o
new file mode 100644
index 0000000000..ca99fab4e9
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.3o
@@ -0,0 +1,22 @@
+
+.TH CanonicalTest 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.CanonicalTest\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Base__List : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Base__ : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Base : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR Base__Tests : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR List_modif : \f[CB]module\fR \f[CB]type\fR \f[CB]of\fR Base\.List \f[CB]with\fR \f[CB]type\fR 'c t = \f[CB]'c\fR Base\.List\.t
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base.3o
new file mode 100644
index 0000000000..448c9ccefd
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base.3o
@@ -0,0 +1,14 @@
+
+.TH Base 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.Base
+.SH Synopsis
+.sp
+.in 2
+\fBModule CanonicalTest\.Base\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR List : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base.List.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base.List.3o
new file mode 100644
index 0000000000..8009af61ee
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base.List.3o
@@ -0,0 +1,16 @@
+
+.TH List 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.Base\.List
+.SH Synopsis
+.sp
+.in 2
+\fBModule Base\.List\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR 'a t
+.sp
+\f[CB]val\fR id : \f[CB]'a\fR t \f[CB]\->\fR \f[CB]'a\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__.3o
new file mode 100644
index 0000000000..0c999843ef
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__.3o
@@ -0,0 +1,14 @@
+
+.TH Base__ 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.Base__
+.SH Synopsis
+.sp
+.in 2
+\fBModule CanonicalTest\.Base__\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR List = Base__List
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__List.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__List.3o
new file mode 100644
index 0000000000..9ca18f3ad6
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__List.3o
@@ -0,0 +1,16 @@
+
+.TH Base__List 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.Base__List
+.SH Synopsis
+.sp
+.in 2
+\fBModule CanonicalTest\.Base__List\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR 'a t
+.sp
+\f[CB]val\fR id : \f[CB]'a\fR t \f[CB]\->\fR \f[CB]'a\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__Tests.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__Tests.3o
new file mode 100644
index 0000000000..fb691f974b
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__Tests.3o
@@ -0,0 +1,33 @@
+
+.TH Base__Tests 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.Base__Tests
+.SH Synopsis
+.sp
+.in 2
+\fBModule CanonicalTest\.Base__Tests\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR C : \f[CB]module\fR \f[CB]type\fR \f[CB]of\fR Base__\.List
+.sp
+\f[CB]module\fR L = Base__\.List
+.sp
+\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 L\.id
+.nf
+.sp
+\f[CB]val\fR baz : \f[CB]'a\fR Base__\.List\.t \f[CB]\->\fR unit
+.fi
+.br
+.ti +2
+Just seeing if Base__\.List\.t (Base__\.List\.t) gets rewriten to Base\.List\.t (Base\.List\.t)
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__Tests.C.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__Tests.C.3o
new file mode 100644
index 0000000000..cc53028a11
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.Base__Tests.C.3o
@@ -0,0 +1,16 @@
+
+.TH C 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.Base__Tests\.C
+.SH Synopsis
+.sp
+.in 2
+\fBModule Base__Tests\.C\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR 'a t
+.sp
+\f[CB]val\fR id : \f[CB]'a\fR t \f[CB]\->\fR \f[CB]'a\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.List_modif.3o b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.List_modif.3o
new file mode 100644
index 0000000000..f388bf1c79
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CanonicalTest.List_modif.3o
@@ -0,0 +1,16 @@
+
+.TH List_modif 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CanonicalTest\.List_modif
+.SH Synopsis
+.sp
+.in 2
+\fBModule CanonicalTest\.List_modif\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR 'c t = \f[CB]'c\fR Base\.List\.t
+.sp
+\f[CB]val\fR id : \f[CB]'a\fR t \f[CB]\->\fR \f[CB]'a\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.CollectionModule.3o b/test/generators/cases_pre408/man/Ocamlary.CollectionModule.3o
new file mode 100644
index 0000000000..42287001e2
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CollectionModule.3o
@@ -0,0 +1,50 @@
+
+.TH CollectionModule 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CollectionModule
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.CollectionModule\fR
+.in
+.sp
+.fi
+This comment is for CollectionModule\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR collection
+.fi
+.br
+.ti +2
+This comment is for collection\.
+.nf
+.sp
+\f[CB]type\fR element
+.sp
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleA\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +4
+This comment is for t\.
+.nf
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleTypeA\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.CollectionModule.InnerModuleA.3o b/test/generators/cases_pre408/man/Ocamlary.CollectionModule.InnerModuleA.3o
new file mode 100644
index 0000000000..b575f1934a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CollectionModule.InnerModuleA.3o
@@ -0,0 +1,48 @@
+
+.TH InnerModuleA 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CollectionModule\.InnerModuleA
+.SH Synopsis
+.sp
+.in 2
+\fBModule CollectionModule\.InnerModuleA\fR
+.in
+.sp
+.fi
+This comment is for InnerModuleA\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +2
+This comment is for t\.
+.nf
+.sp
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleA'\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +4
+This comment is for t\.
+.nf
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleTypeA'\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o b/test/generators/cases_pre408/man/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o
new file mode 100644
index 0000000000..035499870d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o
@@ -0,0 +1,23 @@
+
+.TH InnerModuleA' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.CollectionModule\.InnerModuleA\.InnerModuleA'
+.SH Synopsis
+.sp
+.in 2
+\fBModule InnerModuleA\.InnerModuleA'\fR
+.in
+.sp
+.fi
+This comment is for InnerModuleA'\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +2
+This comment is for t\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep1.3o b/test/generators/cases_pre408/man/Ocamlary.Dep1.3o
new file mode 100644
index 0000000000..297a5aa286
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep1.3o
@@ -0,0 +1,27 @@
+
+.TH Dep1 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep1
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep1\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]class\fR c : \f[CB]object\fR
+.br
+.ti +4
+\f[CB]method\fR m : int
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR X : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep1.X.3o b/test/generators/cases_pre408/man/Ocamlary.Dep1.X.3o
new file mode 100644
index 0000000000..735ada7b3f
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep1.X.3o
@@ -0,0 +1,14 @@
+
+.TH X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep1\.X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Dep1\.X\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Y : S
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep1.X.Y.3o b/test/generators/cases_pre408/man/Ocamlary.Dep1.X.Y.3o
new file mode 100644
index 0000000000..70fb5f99d6
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep1.X.Y.3o
@@ -0,0 +1,14 @@
+
+.TH Y 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep1\.X\.Y
+.SH Synopsis
+.sp
+.in 2
+\fBModule X\.Y\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep1.X.Y.c.3o b/test/generators/cases_pre408/man/Ocamlary.Dep1.X.Y.c.3o
new file mode 100644
index 0000000000..382149a17f
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep1.X.Y.c.3o
@@ -0,0 +1,14 @@
+
+.TH c 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep1\.X\.Y\.c
+.SH Synopsis
+.sp
+.in 2
+\fBClass Y\.c\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]method\fR m : int
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep11.3o b/test/generators/cases_pre408/man/Ocamlary.Dep11.3o
new file mode 100644
index 0000000000..bac56bcd86
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep11.3o
@@ -0,0 +1,25 @@
+
+.TH Dep11 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep11
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep11\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]class\fR c : \f[CB]object\fR
+.br
+.ti +4
+\f[CB]method\fR m : int
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep12.3o b/test/generators/cases_pre408/man/Ocamlary.Dep12.3o
new file mode 100644
index 0000000000..385fd493ff
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep12.3o
@@ -0,0 +1,30 @@
+
+.TH Dep12 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep12
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep12\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR Arg : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR S
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]module\fR \f[CB]type\fR T = Arg\.S
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep13.3o b/test/generators/cases_pre408/man/Ocamlary.Dep13.3o
new file mode 100644
index 0000000000..3f3e4f77cf
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep13.3o
@@ -0,0 +1,14 @@
+
+.TH Dep13 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep13
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep13\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep13.c.3o b/test/generators/cases_pre408/man/Ocamlary.Dep13.c.3o
new file mode 100644
index 0000000000..f3bd02afb7
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep13.c.3o
@@ -0,0 +1,14 @@
+
+.TH c 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep13\.c
+.SH Synopsis
+.sp
+.in 2
+\fBClass Dep13\.c\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]method\fR m : int
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep2.3o b/test/generators/cases_pre408/man/Ocamlary.Dep2.3o
new file mode 100644
index 0000000000..af26563630
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep2.3o
@@ -0,0 +1,41 @@
+
+.TH Dep2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep2
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep2\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR Arg : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR S
+.sp
+.ti +2
+\f[CB]module\fR X : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR Y : S
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]module\fR A : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]module\fR B = A\.Y
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep2.A.3o b/test/generators/cases_pre408/man/Ocamlary.Dep2.A.3o
new file mode 100644
index 0000000000..bfcc73e395
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep2.A.3o
@@ -0,0 +1,14 @@
+
+.TH A 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep2\.A
+.SH Synopsis
+.sp
+.in 2
+\fBModule Dep2\.A\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Y : Arg\.S
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep3.3o b/test/generators/cases_pre408/man/Ocamlary.Dep3.3o
new file mode 100644
index 0000000000..7c9361e264
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep3.3o
@@ -0,0 +1,14 @@
+
+.TH Dep3 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep3
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep3\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR a
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep4.3o b/test/generators/cases_pre408/man/Ocamlary.Dep4.3o
new file mode 100644
index 0000000000..b76c8a2a43
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep4.3o
@@ -0,0 +1,37 @@
+
+.TH Dep4 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep4
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep4\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR b
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR X : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR b
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR Y : \f[CB]sig\fR \f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR X : T
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep4.X.3o b/test/generators/cases_pre408/man/Ocamlary.Dep4.X.3o
new file mode 100644
index 0000000000..b3f7f0447d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep4.X.3o
@@ -0,0 +1,14 @@
+
+.TH X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep4\.X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Dep4\.X\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR b
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep5.3o b/test/generators/cases_pre408/man/Ocamlary.Dep5.3o
new file mode 100644
index 0000000000..17c07611d9
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep5.3o
@@ -0,0 +1,45 @@
+
+.TH Dep5 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep5
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep5\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR Arg : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR T
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR X : T
+.sp
+.ti +4
+\f[CB]module\fR Y : \f[CB]sig\fR \f[CB]end\fR
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR X : T
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]module\fR Z : Arg\.S \f[CB]with\fR \f[CB]module\fR Y = Dep3
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep5.Z.3o b/test/generators/cases_pre408/man/Ocamlary.Dep5.Z.3o
new file mode 100644
index 0000000000..e7b9f53035
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep5.Z.3o
@@ -0,0 +1,16 @@
+
+.TH Z 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep5\.Z
+.SH Synopsis
+.sp
+.in 2
+\fBModule Dep5\.Z\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR X : Arg\.T
+.sp
+\f[CB]module\fR Y = Dep3
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep6.3o b/test/generators/cases_pre408/man/Ocamlary.Dep6.3o
new file mode 100644
index 0000000000..0d2adda841
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep6.3o
@@ -0,0 +1,43 @@
+
+.TH Dep6 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep6
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep6\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR d
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR R = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR d
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR Y : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR d
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR X : T
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep6.X.3o b/test/generators/cases_pre408/man/Ocamlary.Dep6.X.3o
new file mode 100644
index 0000000000..2f29b85e3a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep6.X.3o
@@ -0,0 +1,21 @@
+
+.TH X 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep6\.X
+.SH Synopsis
+.sp
+.in 2
+\fBModule Dep6\.X\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR R = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR d
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR Y : R
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep6.X.Y.3o b/test/generators/cases_pre408/man/Ocamlary.Dep6.X.Y.3o
new file mode 100644
index 0000000000..ede5b1192c
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep6.X.Y.3o
@@ -0,0 +1,14 @@
+
+.TH Y 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep6\.X\.Y
+.SH Synopsis
+.sp
+.in 2
+\fBModule X\.Y\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR d
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep7.3o b/test/generators/cases_pre408/man/Ocamlary.Dep7.3o
new file mode 100644
index 0000000000..489d2662c6
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep7.3o
@@ -0,0 +1,54 @@
+
+.TH Dep7 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep7
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep7\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR Arg : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR S
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR R = S
+.sp
+.ti +4
+\f[CB]module\fR Y : R
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR X : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR R = S
+.sp
+.ti +4
+\f[CB]module\fR Y : R
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]module\fR M : Arg\.T
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep7.M.3o b/test/generators/cases_pre408/man/Ocamlary.Dep7.M.3o
new file mode 100644
index 0000000000..b6ee8492e8
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep7.M.3o
@@ -0,0 +1,16 @@
+
+.TH M 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep7\.M
+.SH Synopsis
+.sp
+.in 2
+\fBModule Dep7\.M\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR R = Arg\.S
+.sp
+\f[CB]module\fR Y : R
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep8.3o b/test/generators/cases_pre408/man/Ocamlary.Dep8.3o
new file mode 100644
index 0000000000..f669090526
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep8.3o
@@ -0,0 +1,19 @@
+
+.TH Dep8 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep8
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep8\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.Dep9.3o b/test/generators/cases_pre408/man/Ocamlary.Dep9.3o
new file mode 100644
index 0000000000..16b206a86f
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Dep9.3o
@@ -0,0 +1,30 @@
+
+.TH Dep9 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Dep9
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Dep9\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR X : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR T
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]module\fR \f[CB]type\fR T = X\.T
diff --git a/test/generators/cases_pre408/man/Ocamlary.DoubleInclude1.3o b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude1.3o
new file mode 100644
index 0000000000..7d675b3213
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude1.3o
@@ -0,0 +1,14 @@
+
+.TH DoubleInclude1 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.DoubleInclude1
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.DoubleInclude1\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR DoubleInclude2 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.DoubleInclude1.DoubleInclude2.3o b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude1.DoubleInclude2.3o
new file mode 100644
index 0000000000..c81b84ccb9
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude1.DoubleInclude2.3o
@@ -0,0 +1,14 @@
+
+.TH DoubleInclude2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.DoubleInclude1\.DoubleInclude2
+.SH Synopsis
+.sp
+.in 2
+\fBModule DoubleInclude1\.DoubleInclude2\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR double_include
diff --git a/test/generators/cases_pre408/man/Ocamlary.DoubleInclude3.3o b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude3.3o
new file mode 100644
index 0000000000..d56c24133e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude3.3o
@@ -0,0 +1,14 @@
+
+.TH DoubleInclude3 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.DoubleInclude3
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.DoubleInclude3\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR DoubleInclude2 : \f[CB]sig\fR \.\.\. \f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.DoubleInclude3.DoubleInclude2.3o b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude3.DoubleInclude2.3o
new file mode 100644
index 0000000000..18dc61f14d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.DoubleInclude3.DoubleInclude2.3o
@@ -0,0 +1,14 @@
+
+.TH DoubleInclude2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.DoubleInclude3\.DoubleInclude2
+.SH Synopsis
+.sp
+.in 2
+\fBModule DoubleInclude3\.DoubleInclude2\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR double_include
diff --git a/test/generators/cases_pre408/man/Ocamlary.Empty.3o b/test/generators/cases_pre408/man/Ocamlary.Empty.3o
new file mode 100644
index 0000000000..1ce04df962
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Empty.3o
@@ -0,0 +1,21 @@
+
+.TH Empty 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Empty
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Empty\fR
+.in
+.sp
+.fi
+A plain, empty module
+.nf
+.sp
+.fi
+This module has a signature without any members\.
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.ExtMod.3o b/test/generators/cases_pre408/man/Ocamlary.ExtMod.3o
new file mode 100644
index 0000000000..9b6c8ba8e4
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.ExtMod.3o
@@ -0,0 +1,21 @@
+
+.TH ExtMod 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.ExtMod
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.ExtMod\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = \.\.
+.sp
+\f[CB]type\fR t +=
+.br
+.ti +2
+| \f[CB]Leisureforce\fR
+.br
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.FunctorTypeOf.3o b/test/generators/cases_pre408/man/Ocamlary.FunctorTypeOf.3o
new file mode 100644
index 0000000000..576599a8bf
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.FunctorTypeOf.3o
@@ -0,0 +1,133 @@
+
+.TH FunctorTypeOf 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.FunctorTypeOf
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.FunctorTypeOf\fR
+.in
+.sp
+.fi
+This comment is for FunctorTypeOf\.
+.nf
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR Collection : \f[CB]sig\fR
+.br
+.ti +2
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +2
+\f[CB]type\fR collection
+.fi
+.br
+.ti +4
+This comment is for collection\.
+.nf
+.sp
+.ti +2
+\f[CB]type\fR element
+.sp
+.ti +2
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]type\fR t = Collection\.collection
+.fi
+.br
+.ti +2
+This comment is for t\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.IncludeInclude1.3o b/test/generators/cases_pre408/man/Ocamlary.IncludeInclude1.3o
new file mode 100644
index 0000000000..2d1d137d14
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.IncludeInclude1.3o
@@ -0,0 +1,19 @@
+
+.TH IncludeInclude1 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.IncludeInclude1
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.IncludeInclude1\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR IncludeInclude2 = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR include_include
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.IncludedA.3o b/test/generators/cases_pre408/man/Ocamlary.IncludedA.3o
new file mode 100644
index 0000000000..3f4bb80a5c
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.IncludedA.3o
@@ -0,0 +1,14 @@
+
+.TH IncludedA 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.IncludedA
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.IncludedA\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.M.3o b/test/generators/cases_pre408/man/Ocamlary.M.3o
new file mode 100644
index 0000000000..76aa8ee82a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.M.3o
@@ -0,0 +1,14 @@
+
+.TH M 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.M
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.M\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.ModuleWithSignature.3o b/test/generators/cases_pre408/man/Ocamlary.ModuleWithSignature.3o
new file mode 100644
index 0000000000..cfd75b9598
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.ModuleWithSignature.3o
@@ -0,0 +1,17 @@
+
+.TH ModuleWithSignature 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.ModuleWithSignature
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.ModuleWithSignature\fR
+.in
+.sp
+.fi
+A plain module of a signature of \f[CI]EmptySig\fR (reference)
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.ModuleWithSignatureAlias.3o b/test/generators/cases_pre408/man/Ocamlary.ModuleWithSignatureAlias.3o
new file mode 100644
index 0000000000..e3d13776c3
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.ModuleWithSignatureAlias.3o
@@ -0,0 +1,21 @@
+
+.TH ModuleWithSignatureAlias 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.ModuleWithSignatureAlias
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.ModuleWithSignatureAlias\fR
+.in
+.sp
+.fi
+A plain module with an alias signature
+.nf
+.sp
+.fi
+@deprecated: I don't like this element any more\.
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.One.3o b/test/generators/cases_pre408/man/Ocamlary.One.3o
new file mode 100644
index 0000000000..391b8daa38
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.One.3o
@@ -0,0 +1,14 @@
+
+.TH One 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.One
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.One\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR one
diff --git a/test/generators/cases_pre408/man/Ocamlary.Only_a_module.3o b/test/generators/cases_pre408/man/Ocamlary.Only_a_module.3o
new file mode 100644
index 0000000000..c0d805671a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Only_a_module.3o
@@ -0,0 +1,14 @@
+
+.TH Only_a_module 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Only_a_module
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Only_a_module\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.Recollection.3o b/test/generators/cases_pre408/man/Ocamlary.Recollection.3o
new file mode 100644
index 0000000000..838559c75a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Recollection.3o
@@ -0,0 +1,161 @@
+
+.TH Recollection 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Recollection
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.Recollection\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR C : \f[CB]sig\fR
+.br
+.ti +2
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+.ti +2
+\f[CB]type\fR collection
+.fi
+.br
+.ti +4
+This comment is for collection\.
+.nf
+.sp
+.ti +2
+\f[CB]type\fR element
+.sp
+.ti +2
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleA'\.
+.nf
+.sp
+.ti +4
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +6
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +8
+This comment is for t\.
+.nf
+
+.br
+.ti +4
+\f[CB]end\fR
+.fi
+.br
+.ti +6
+This comment is for InnerModuleTypeA'\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleA\.
+.nf
+.sp
+.ti +2
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +6
+This comment is for t\.
+.nf
+
+.br
+.ti +2
+\f[CB]end\fR
+.fi
+.br
+.ti +4
+This comment is for InnerModuleTypeA\.
+.nf
+
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+.fi
+This comment is for CollectionModule\.
+.nf
+.sp
+\f[CB]type\fR collection = C\.element list
+.fi
+.br
+.ti +2
+This comment is for collection\.
+.nf
+.sp
+\f[CB]type\fR element = C\.collection
+.sp
+\f[CB]module\fR InnerModuleA : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleA\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t = InnerModuleA\.InnerModuleA'\.t
+.fi
+.br
+.ti +4
+This comment is for t\.
+.nf
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleTypeA\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.Recollection.InnerModuleA.3o b/test/generators/cases_pre408/man/Ocamlary.Recollection.InnerModuleA.3o
new file mode 100644
index 0000000000..8deaf3fa24
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Recollection.InnerModuleA.3o
@@ -0,0 +1,48 @@
+
+.TH InnerModuleA 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Recollection\.InnerModuleA
+.SH Synopsis
+.sp
+.in 2
+\fBModule Recollection\.InnerModuleA\fR
+.in
+.sp
+.fi
+This comment is for InnerModuleA\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = collection
+.fi
+.br
+.ti +2
+This comment is for t\.
+.nf
+.sp
+\f[CB]module\fR InnerModuleA' : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleA'\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR InnerModuleTypeA' = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t = InnerModuleA'\.t
+.fi
+.br
+.ti +4
+This comment is for t\.
+.nf
+
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+This comment is for InnerModuleTypeA'\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o b/test/generators/cases_pre408/man/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o
new file mode 100644
index 0000000000..65079cfb7a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o
@@ -0,0 +1,23 @@
+
+.TH InnerModuleA' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.Recollection\.InnerModuleA\.InnerModuleA'
+.SH Synopsis
+.sp
+.in 2
+\fBModule InnerModuleA\.InnerModuleA'\fR
+.in
+.sp
+.fi
+This comment is for InnerModuleA'\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t = (unit, unit) a_function
+.fi
+.br
+.ti +2
+This comment is for t\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.With10.3o b/test/generators/cases_pre408/man/Ocamlary.With10.3o
new file mode 100644
index 0000000000..368fda0a35
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With10.3o
@@ -0,0 +1,34 @@
+
+.TH With10 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With10
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With10\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR M : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR S
+.br
+.ti +2
+\f[CB]end\fR
+.sp
+.ti +2
+\f[CB]module\fR N : M\.S
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+\f[CI]With10\.T\fR is a submodule type\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.With2.3o b/test/generators/cases_pre408/man/Ocamlary.With2.3o
new file mode 100644
index 0000000000..1f6b6489a8
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With2.3o
@@ -0,0 +1,19 @@
+
+.TH With2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With2
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With2\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.With3.3o b/test/generators/cases_pre408/man/Ocamlary.With3.3o
new file mode 100644
index 0000000000..212ac4640e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With3.3o
@@ -0,0 +1,16 @@
+
+.TH With3 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With3
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With3\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR M = With2
+.sp
+\f[CB]module\fR N : M\.S
diff --git a/test/generators/cases_pre408/man/Ocamlary.With3.N.3o b/test/generators/cases_pre408/man/Ocamlary.With3.N.3o
new file mode 100644
index 0000000000..abfb61b5ac
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With3.N.3o
@@ -0,0 +1,14 @@
+
+.TH N 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With3\.N
+.SH Synopsis
+.sp
+.in 2
+\fBModule With3\.N\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.With4.3o b/test/generators/cases_pre408/man/Ocamlary.With4.3o
new file mode 100644
index 0000000000..7f10b9a573
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With4.3o
@@ -0,0 +1,14 @@
+
+.TH With4 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With4
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With4\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR N : With2\.S
diff --git a/test/generators/cases_pre408/man/Ocamlary.With4.N.3o b/test/generators/cases_pre408/man/Ocamlary.With4.N.3o
new file mode 100644
index 0000000000..db548b7ba3
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With4.N.3o
@@ -0,0 +1,14 @@
+
+.TH N 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With4\.N
+.SH Synopsis
+.sp
+.in 2
+\fBModule With4\.N\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.With5.3o b/test/generators/cases_pre408/man/Ocamlary.With5.3o
new file mode 100644
index 0000000000..69f001fb2e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With5.3o
@@ -0,0 +1,21 @@
+
+.TH With5 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With5
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With5\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.sp
+\f[CB]module\fR N : S
diff --git a/test/generators/cases_pre408/man/Ocamlary.With5.N.3o b/test/generators/cases_pre408/man/Ocamlary.With5.N.3o
new file mode 100644
index 0000000000..d9965425d3
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With5.N.3o
@@ -0,0 +1,14 @@
+
+.TH N 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With5\.N
+.SH Synopsis
+.sp
+.in 2
+\fBModule With5\.N\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Ocamlary.With6.3o b/test/generators/cases_pre408/man/Ocamlary.With6.3o
new file mode 100644
index 0000000000..47296cc7ab
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With6.3o
@@ -0,0 +1,28 @@
+
+.TH With6 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With6
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With6\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR M : \f[CB]sig\fR
+.br
+.ti +4
+\f[CB]module\fR \f[CB]type\fR S
+.sp
+.ti +4
+\f[CB]module\fR N : S
+.br
+.ti +2
+\f[CB]end\fR
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.With7.3o b/test/generators/cases_pre408/man/Ocamlary.With7.3o
new file mode 100644
index 0000000000..d840e8344a
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With7.3o
@@ -0,0 +1,30 @@
+
+.TH With7 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With7
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With7\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+.sp
+.in 3
+\fB1 Parameters\fR
+.in
+.sp
+\f[CB]module\fR X : \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]module\fR \f[CB]type\fR T
+.br
+\f[CB]end\fR
+.sp
+.in 3
+\fB2 Signature\fR
+.in
+.sp
+\f[CB]module\fR \f[CB]type\fR T = X\.T
diff --git a/test/generators/cases_pre408/man/Ocamlary.With9.3o b/test/generators/cases_pre408/man/Ocamlary.With9.3o
new file mode 100644
index 0000000000..c9b53e7976
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.With9.3o
@@ -0,0 +1,19 @@
+
+.TH With9 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.With9
+.SH Synopsis
+.sp
+.in 2
+\fBModule Ocamlary\.With9\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.empty_class.3o b/test/generators/cases_pre408/man/Ocamlary.empty_class.3o
new file mode 100644
index 0000000000..89eec5c77c
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.empty_class.3o
@@ -0,0 +1,14 @@
+
+.TH empty_class 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.empty_class
+.SH Synopsis
+.sp
+.in 2
+\fBClass Ocamlary\.empty_class\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Ocamlary.one_method_class.3o b/test/generators/cases_pre408/man/Ocamlary.one_method_class.3o
new file mode 100644
index 0000000000..92d557d691
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.one_method_class.3o
@@ -0,0 +1,14 @@
+
+.TH one_method_class 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.one_method_class
+.SH Synopsis
+.sp
+.in 2
+\fBClass Ocamlary\.one_method_class\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]method\fR go : unit
diff --git a/test/generators/cases_pre408/man/Ocamlary.param_class.3o b/test/generators/cases_pre408/man/Ocamlary.param_class.3o
new file mode 100644
index 0000000000..10086f0dac
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.param_class.3o
@@ -0,0 +1,14 @@
+
+.TH param_class 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.param_class
+.SH Synopsis
+.sp
+.in 2
+\fBClass Ocamlary\.param_class\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]method\fR v : \f[CB]'a\fR
diff --git a/test/generators/cases_pre408/man/Ocamlary.two_method_class.3o b/test/generators/cases_pre408/man/Ocamlary.two_method_class.3o
new file mode 100644
index 0000000000..2a4cd7ba57
--- /dev/null
+++ b/test/generators/cases_pre408/man/Ocamlary.two_method_class.3o
@@ -0,0 +1,16 @@
+
+.TH two_method_class 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Ocamlary\.two_method_class
+.SH Synopsis
+.sp
+.in 2
+\fBClass Ocamlary\.two_method_class\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]method\fR one : one_method_class
+.sp
+\f[CB]method\fR undo : unit
diff --git a/test/man/expect/test_package+ml/Section.3o b/test/generators/cases_pre408/man/Section.3o
similarity index 97%
rename from test/man/expect/test_package+ml/Section.3o
rename to test/generators/cases_pre408/man/Section.3o
index 474a7299e6..d39edf6283 100644
--- a/test/man/expect/test_package+ml/Section.3o
+++ b/test/generators/cases_pre408/man/Section.3o
@@ -1,7 +1,7 @@
.TH Section 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Section
+test\.Section
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Stop.3o b/test/generators/cases_pre408/man/Stop.3o
similarity index 97%
rename from test/man/expect/test_package+ml/Stop.3o
rename to test/generators/cases_pre408/man/Stop.3o
index 48f11ad6ba..867b2d02f2 100644
--- a/test/man/expect/test_package+ml/Stop.3o
+++ b/test/generators/cases_pre408/man/Stop.3o
@@ -1,7 +1,7 @@
.TH Stop 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Stop
+test\.Stop
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/Stop.N.3o b/test/generators/cases_pre408/man/Stop.N.3o
new file mode 100644
index 0000000000..4f48195770
--- /dev/null
+++ b/test/generators/cases_pre408/man/Stop.N.3o
@@ -0,0 +1,14 @@
+
+.TH N 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Stop\.N
+.SH Synopsis
+.sp
+.in 2
+\fBModule Stop\.N\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]val\fR quux : int
diff --git a/test/generators/cases_pre408/man/Stop_dead_link_doc.3o b/test/generators/cases_pre408/man/Stop_dead_link_doc.3o
new file mode 100644
index 0000000000..42da7b9d5e
--- /dev/null
+++ b/test/generators/cases_pre408/man/Stop_dead_link_doc.3o
@@ -0,0 +1,52 @@
+
+.TH Stop_dead_link_doc 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Stop_dead_link_doc
+.SH Synopsis
+.sp
+.in 2
+\fBModule Stop_dead_link_doc\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR Foo : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.sp
+\f[CB]type\fR foo =
+.br
+.ti +2
+| \f[CB]Bar\fR \f[CB]of\fR Foo\.t
+.br
+.sp
+\f[CB]type\fR bar =
+.br
+.ti +2
+| \f[CB]Bar\fR \f[CB]of\fR {
+.br
+.ti +6
+field : Foo\.t;
+.br
+.ti +4
+}
+.br
+.sp
+\f[CB]type\fR foo_ =
+.br
+.ti +2
+| \f[CB]Bar_\fR \f[CB]of\fR int * Foo\.t * int
+.br
+.sp
+\f[CB]type\fR bar_ =
+.br
+.ti +2
+| \f[CB]Bar__\fR \f[CB]of\fR Foo\.t option
+.br
+.sp
+\f[CB]type\fR another_foo
+.sp
+\f[CB]type\fR another_bar
+.sp
+\f[CB]type\fR another_foo_
+.sp
+\f[CB]type\fR another_bar_
diff --git a/test/generators/cases_pre408/man/Stop_dead_link_doc.Foo.3o b/test/generators/cases_pre408/man/Stop_dead_link_doc.Foo.3o
new file mode 100644
index 0000000000..c64f3b61a5
--- /dev/null
+++ b/test/generators/cases_pre408/man/Stop_dead_link_doc.Foo.3o
@@ -0,0 +1,14 @@
+
+.TH Foo 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Stop_dead_link_doc\.Foo
+.SH Synopsis
+.sp
+.in 2
+\fBModule Stop_dead_link_doc\.Foo\fR
+.in
+.sp
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.3o b/test/generators/cases_pre408/man/Toplevel_comments.3o
new file mode 100644
index 0000000000..1d92f8b60d
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.3o
@@ -0,0 +1,115 @@
+
+.TH Toplevel_comments 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\fR
+.in
+.sp
+.fi
+A doc comment at the beginning of a module is considered to be that module's doc\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]module\fR \f[CB]type\fR T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of T, part 1\.
+.nf
+.sp
+\f[CB]module\fR Include_inline : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of T, part 2\.
+.nf
+.sp
+\f[CB]module\fR Include_inline' : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of Include_inline, part 1\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR Include_inline_T = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of T, part 2\.
+.nf
+.sp
+\f[CB]module\fR \f[CB]type\fR Include_inline_T' = \f[CB]sig\fR
+.br
+.ti +2
+\f[CB]type\fR t
+.br
+\f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of Include_inline_T', part 1\.
+.nf
+.sp
+\f[CB]module\fR M : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of M
+.nf
+.sp
+\f[CB]module\fR M' : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of M' from outside
+.nf
+.sp
+\f[CB]module\fR M'' : \f[CB]sig\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of M'', part 1\.
+.nf
+.sp
+\f[CB]module\fR Alias : T
+.fi
+.br
+.ti +2
+Doc of Alias\.
+.nf
+.sp
+\f[CB]class\fR c1 : int \f[CB]\->\fR \f[CB]object\fR \.\.\. \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of c1, part 1\.
+.nf
+.sp
+\f[CB]class\fR \f[CB]type\fR ct = \f[CB]object\fR \f[CB]end\fR
+.fi
+.br
+.ti +2
+Doc of ct, part 1\.
+.nf
+.sp
+\f[CB]class\fR c2 : ct
+.fi
+.br
+.ti +2
+Doc of c2\.
+.nf
+
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.Alias.3o b/test/generators/cases_pre408/man/Toplevel_comments.Alias.3o
new file mode 100644
index 0000000000..1f93d27a59
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.Alias.3o
@@ -0,0 +1,21 @@
+
+.TH Alias 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.Alias
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\.Alias\fR
+.in
+.sp
+.fi
+Doc of Alias\.
+.nf
+.sp
+.fi
+Doc of T, part 2\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.Include_inline'.3o b/test/generators/cases_pre408/man/Toplevel_comments.Include_inline'.3o
new file mode 100644
index 0000000000..9d276557dd
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.Include_inline'.3o
@@ -0,0 +1,21 @@
+
+.TH Include_inline' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.Include_inline'
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\.Include_inline'\fR
+.in
+.sp
+.fi
+Doc of Include_inline, part 1\.
+.nf
+.sp
+.fi
+Doc of Include_inline, part 2\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.Include_inline.3o b/test/generators/cases_pre408/man/Toplevel_comments.Include_inline.3o
new file mode 100644
index 0000000000..e54b041682
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.Include_inline.3o
@@ -0,0 +1,17 @@
+
+.TH Include_inline 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.Include_inline
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\.Include_inline\fR
+.in
+.sp
+.fi
+Doc of T, part 2\.
+.nf
+.SH Documentation
+.sp
+.nf
+\f[CB]type\fR t
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.M''.3o b/test/generators/cases_pre408/man/Toplevel_comments.M''.3o
new file mode 100644
index 0000000000..8d9f3c36ea
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.M''.3o
@@ -0,0 +1,21 @@
+
+.TH M'' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.M''
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\.M''\fR
+.in
+.sp
+.fi
+Doc of M'', part 1\.
+.nf
+.sp
+.fi
+Doc of M'', part 2\.
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.M'.3o b/test/generators/cases_pre408/man/Toplevel_comments.M'.3o
new file mode 100644
index 0000000000..e373585db6
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.M'.3o
@@ -0,0 +1,17 @@
+
+.TH M' 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.M'
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\.M'\fR
+.in
+.sp
+.fi
+Doc of M' from outside
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.M.3o b/test/generators/cases_pre408/man/Toplevel_comments.M.3o
new file mode 100644
index 0000000000..39c93b9f03
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.M.3o
@@ -0,0 +1,17 @@
+
+.TH M 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.M
+.SH Synopsis
+.sp
+.in 2
+\fBModule Toplevel_comments\.M\fR
+.in
+.sp
+.fi
+Doc of M
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.c1.3o b/test/generators/cases_pre408/man/Toplevel_comments.c1.3o
new file mode 100644
index 0000000000..43a3ae2b18
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.c1.3o
@@ -0,0 +1,21 @@
+
+.TH c1 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.c1
+.SH Synopsis
+.sp
+.in 2
+\fBClass Toplevel_comments\.c1\fR
+.in
+.sp
+.fi
+Doc of c1, part 1\.
+.nf
+.sp
+.fi
+Doc of c1, part 2\.
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/generators/cases_pre408/man/Toplevel_comments.c2.3o b/test/generators/cases_pre408/man/Toplevel_comments.c2.3o
new file mode 100644
index 0000000000..50bf9f61dd
--- /dev/null
+++ b/test/generators/cases_pre408/man/Toplevel_comments.c2.3o
@@ -0,0 +1,21 @@
+
+.TH c2 3 "" "Odoc" "OCaml Library"
+.SH Name
+test\.Toplevel_comments\.c2
+.SH Synopsis
+.sp
+.in 2
+\fBClass Toplevel_comments\.c2\fR
+.in
+.sp
+.fi
+Doc of c2\.
+.nf
+.sp
+.fi
+Doc of ct, part 2\.
+.nf
+.SH Documentation
+.sp
+.nf
+
diff --git a/test/man/expect/test_package+ml/Type.3o b/test/generators/cases_pre408/man/Type.3o
similarity index 99%
rename from test/man/expect/test_package+ml/Type.3o
rename to test/generators/cases_pre408/man/Type.3o
index 4a1cb7770b..9ff7f47853 100644
--- a/test/man/expect/test_package+ml/Type.3o
+++ b/test/generators/cases_pre408/man/Type.3o
@@ -1,7 +1,7 @@
.TH Type 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Type
+test\.Type
.SH Synopsis
.sp
.in 2
diff --git a/test/man/expect/test_package+ml/Val.3o b/test/generators/cases_pre408/man/Val.3o
similarity index 93%
rename from test/man/expect/test_package+ml/Val.3o
rename to test/generators/cases_pre408/man/Val.3o
index ed10f94e48..f895a8b967 100644
--- a/test/man/expect/test_package+ml/Val.3o
+++ b/test/generators/cases_pre408/man/Val.3o
@@ -1,7 +1,7 @@
.TH Val 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.Val
+test\.Val
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/cases_pre408/man/dune b/test/generators/cases_pre408/man/dune
new file mode 100644
index 0000000000..985a2da3ef
--- /dev/null
+++ b/test/generators/cases_pre408/man/dune
@@ -0,0 +1 @@
+(include man.dune.inc)
diff --git a/test/generators/cases_pre408/man/gen_man/dune b/test/generators/cases_pre408/man/gen_man/dune
new file mode 100644
index 0000000000..c282dcce51
--- /dev/null
+++ b/test/generators/cases_pre408/man/gen_man/dune
@@ -0,0 +1,5 @@
+(executable
+ (name gen_man)
+ (libraries man_t_rule)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/cases_pre408/man/gen_man/gen_man.ml b/test/generators/cases_pre408/man/gen_man/gen_man.ml
new file mode 100644
index 0000000000..fce1a46486
--- /dev/null
+++ b/test/generators/cases_pre408/man/gen_man/gen_man.ml
@@ -0,0 +1,6 @@
+let () =
+ let stanzas =
+ Gen_backend.gen_backend_rules "man" Man_t_rule.man_target_rule
+ Gen_backend.files "4.10"
+ in
+ List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas
diff --git a/test/generators/cases_pre408/man/man.dune.inc b/test/generators/cases_pre408/man/man.dune.inc
new file mode 100644
index 0000000000..342633e189
--- /dev/null
+++ b/test/generators/cases_pre408/man/man.dune.inc
@@ -0,0 +1,1670 @@
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../alias.odocl})
+ (with-stdout-to
+ Alias.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Alias.3o'")))
+ (with-stdout-to
+ Alias.Foo__X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Alias.Foo__X.3o'")))
+ (with-stdout-to
+ Alias.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Alias.X.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.3o Alias.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.Foo__X.3o Alias.Foo__X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Alias.X.3o Alias.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../bugs.odocl})
+ (with-stdout-to
+ Bugs.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Bugs.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs.3o Bugs.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../bugs_pre_410.odocl})
+ (with-stdout-to
+ Bugs_pre_410.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Bugs_pre_410.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Bugs_pre_410.3o Bugs_pre_410.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../class.odocl})
+ (with-stdout-to
+ Class.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Class.3o'")))
+ (with-stdout-to
+ Class.mutually'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Class.mutually'\\''.3o'")))
+ (with-stdout-to
+ Class.recursive'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Class.recursive'\\''.3o'")))
+ (with-stdout-to
+ Class.empty_virtual'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Class.empty_virtual'\\''.3o'")))
+ (with-stdout-to
+ Class.polymorphic'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Class.polymorphic'\\''.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.3o Class.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.mutually'.3o Class.mutually'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.recursive'.3o Class.recursive'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.empty_virtual'.3o Class.empty_virtual'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Class.polymorphic'.3o Class.polymorphic'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../external.odocl})
+ (with-stdout-to
+ External.3o.gen
+ (progn
+ (system "cat 'man.gen/test/External.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff External.3o External.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../functor.odocl})
+ (with-stdout-to
+ Functor.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor.3o'")))
+ (with-stdout-to
+ Functor.F1.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor.F1.3o'")))
+ (with-stdout-to
+ Functor.F2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor.F2.3o'")))
+ (with-stdout-to
+ Functor.F3.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor.F3.3o'")))
+ (with-stdout-to
+ Functor.F4.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor.F4.3o'")))
+ (with-stdout-to
+ Functor.F5.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor.F5.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.3o Functor.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F1.3o Functor.F1.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F2.3o Functor.F2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F3.3o Functor.F3.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F4.3o Functor.F4.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor.F5.3o Functor.F5.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../functor2.odocl})
+ (with-stdout-to
+ Functor2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor2.3o'")))
+ (with-stdout-to
+ Functor2.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Functor2.X.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor2.3o Functor2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Functor2.X.3o Functor2.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../include.odocl})
+ (with-stdout-to
+ Include.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include.3o Include.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../include2.odocl})
+ (with-stdout-to
+ Include2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include2.3o'")))
+ (with-stdout-to
+ Include2.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include2.X.3o'")))
+ (with-stdout-to
+ Include2.Y.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include2.Y.3o'")))
+ (with-stdout-to
+ Include2.Y_include_synopsis.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include2.Y_include_synopsis.3o'")))
+ (with-stdout-to
+ Include2.Y_include_doc.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include2.Y_include_doc.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.3o Include2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.X.3o Include2.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.Y.3o Include2.Y.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.Y_include_synopsis.3o Include2.Y_include_synopsis.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include2.Y_include_doc.3o Include2.Y_include_doc.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../include_sections.odocl})
+ (with-stdout-to
+ Include_sections.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Include_sections.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Include_sections.3o Include_sections.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../interlude.odocl})
+ (with-stdout-to
+ Interlude.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Interlude.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Interlude.3o Interlude.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../markup.odocl})
+ (with-stdout-to
+ Markup.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Markup.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Markup.3o Markup.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../page-mld.odocl})
+ (with-stdout-to
+ mld.3o.gen
+ (progn
+ (system "cat 'man.gen/test/mld.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff mld.3o mld.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../module.odocl})
+ (with-stdout-to
+ Module.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Module.3o'")))
+ (with-stdout-to
+ Module.M'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Module.M'\\''.3o'")))
+ (with-stdout-to
+ Module.Mutually.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Module.Mutually.3o'")))
+ (with-stdout-to
+ Module.Recursive.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Module.Recursive.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.3o Module.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.M'.3o Module.M'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.Mutually.3o Module.Mutually.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Module.Recursive.3o Module.Recursive.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../nested.odocl})
+ (with-stdout-to
+ Nested.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Nested.3o'")))
+ (with-stdout-to
+ Nested.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Nested.X.3o'")))
+ (with-stdout-to
+ Nested.F.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Nested.F.3o'")))
+ (with-stdout-to
+ Nested.z.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Nested.z.3o'")))
+ (with-stdout-to
+ Nested.inherits.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Nested.inherits.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.3o Nested.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.X.3o Nested.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.F.3o Nested.F.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.z.3o Nested.z.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Nested.inherits.3o Nested.inherits.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../ocamlary.odocl})
+ (with-stdout-to
+ Ocamlary.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.3o'")))
+ (with-stdout-to
+ Ocamlary.Empty.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Empty.3o'")))
+ (with-stdout-to
+ Ocamlary.ModuleWithSignature.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.ModuleWithSignature.3o'")))
+ (with-stdout-to
+ Ocamlary.ModuleWithSignatureAlias.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.ModuleWithSignatureAlias.3o'")))
+ (with-stdout-to
+ Ocamlary.One.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.One.3o'")))
+ (with-stdout-to
+ Ocamlary.Buffer.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Buffer.3o'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CollectionModule.3o'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.InnerModuleA.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CollectionModule.InnerModuleA.3o'")))
+ (with-stdout-to
+ Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o.gen
+ (progn
+ (system
+ "cat 'man.gen/test/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'\\''.3o'")))
+ (with-stdout-to
+ Ocamlary.Recollection.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Recollection.3o'")))
+ (with-stdout-to
+ Ocamlary.Recollection.InnerModuleA.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Recollection.InnerModuleA.3o'")))
+ (with-stdout-to
+ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o.gen
+ (progn
+ (system
+ "cat 'man.gen/test/Ocamlary.Recollection.InnerModuleA.InnerModuleA'\\''.3o'")))
+ (with-stdout-to
+ Ocamlary.FunctorTypeOf.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.FunctorTypeOf.3o'")))
+ (with-stdout-to
+ Ocamlary.IncludedA.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.IncludedA.3o'")))
+ (with-stdout-to
+ Ocamlary.ExtMod.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.ExtMod.3o'")))
+ (with-stdout-to
+ Ocamlary.empty_class.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.empty_class.3o'")))
+ (with-stdout-to
+ Ocamlary.one_method_class.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.one_method_class.3o'")))
+ (with-stdout-to
+ Ocamlary.two_method_class.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.two_method_class.3o'")))
+ (with-stdout-to
+ Ocamlary.param_class.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.param_class.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep1.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep1.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep1.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep1.X.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep1.X.Y.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep1.X.Y.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep1.X.Y.c.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep1.X.Y.c.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep2.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep2.A.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep2.A.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep3.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep3.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep4.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep4.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep4.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep4.X.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep5.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep5.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep5.Z.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep5.Z.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep6.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep6.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep6.X.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep6.X.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep6.X.Y.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep6.X.Y.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep7.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep7.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep7.M.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep7.M.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep8.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep8.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep9.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep9.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep11.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep11.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep12.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep12.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep13.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep13.3o'")))
+ (with-stdout-to
+ Ocamlary.Dep13.c.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Dep13.c.3o'")))
+ (with-stdout-to
+ Ocamlary.With2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With2.3o'")))
+ (with-stdout-to
+ Ocamlary.With3.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With3.3o'")))
+ (with-stdout-to
+ Ocamlary.With3.N.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With3.N.3o'")))
+ (with-stdout-to
+ Ocamlary.With4.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With4.3o'")))
+ (with-stdout-to
+ Ocamlary.With4.N.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With4.N.3o'")))
+ (with-stdout-to
+ Ocamlary.With5.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With5.3o'")))
+ (with-stdout-to
+ Ocamlary.With5.N.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With5.N.3o'")))
+ (with-stdout-to
+ Ocamlary.With6.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With6.3o'")))
+ (with-stdout-to
+ Ocamlary.With7.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With7.3o'")))
+ (with-stdout-to
+ Ocamlary.With9.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With9.3o'")))
+ (with-stdout-to
+ Ocamlary.With10.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.With10.3o'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude1.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.DoubleInclude1.3o'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude1.DoubleInclude2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.DoubleInclude1.DoubleInclude2.3o'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude3.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.DoubleInclude3.3o'")))
+ (with-stdout-to
+ Ocamlary.DoubleInclude3.DoubleInclude2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.DoubleInclude3.DoubleInclude2.3o'")))
+ (with-stdout-to
+ Ocamlary.IncludeInclude1.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.IncludeInclude1.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__List.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.Base__List.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.Base__.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.Base.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base.List.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.Base.List.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__Tests.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.Base__Tests.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.Base__Tests.C.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.Base__Tests.C.3o'")))
+ (with-stdout-to
+ Ocamlary.CanonicalTest.List_modif.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.CanonicalTest.List_modif.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__A.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo__A.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__B.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo__B.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__C.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo__C.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__D.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo__D.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__E.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo__E.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo__.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo__.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.A.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo.A.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.B.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo.B.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.C.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo.C.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.D.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo.D.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Foo.E.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Foo.E.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.Std.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.Std.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.E.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.E.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.P1.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.P1.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.P1.Y.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.P1.Y.3o'")))
+ (with-stdout-to
+ Ocamlary.Aliases.P2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Aliases.P2.3o'")))
+ (with-stdout-to
+ Ocamlary.M.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.M.3o'")))
+ (with-stdout-to
+ Ocamlary.Only_a_module.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Ocamlary.Only_a_module.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.3o Ocamlary.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Empty.3o Ocamlary.Empty.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.ModuleWithSignature.3o Ocamlary.ModuleWithSignature.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.ModuleWithSignatureAlias.3o
+ Ocamlary.ModuleWithSignatureAlias.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.One.3o Ocamlary.One.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Buffer.3o Ocamlary.Buffer.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.CollectionModule.3o Ocamlary.CollectionModule.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.InnerModuleA.3o
+ Ocamlary.CollectionModule.InnerModuleA.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o
+ Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Recollection.3o Ocamlary.Recollection.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.InnerModuleA.3o
+ Ocamlary.Recollection.InnerModuleA.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o
+ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.FunctorTypeOf.3o Ocamlary.FunctorTypeOf.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.IncludedA.3o Ocamlary.IncludedA.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.ExtMod.3o Ocamlary.ExtMod.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.empty_class.3o Ocamlary.empty_class.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.one_method_class.3o Ocamlary.one_method_class.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.two_method_class.3o Ocamlary.two_method_class.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.param_class.3o Ocamlary.param_class.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.3o Ocamlary.Dep1.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.X.3o Ocamlary.Dep1.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.X.Y.3o Ocamlary.Dep1.X.Y.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep1.X.Y.c.3o Ocamlary.Dep1.X.Y.c.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep2.3o Ocamlary.Dep2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep2.A.3o Ocamlary.Dep2.A.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep3.3o Ocamlary.Dep3.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep4.3o Ocamlary.Dep4.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep4.X.3o Ocamlary.Dep4.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep5.3o Ocamlary.Dep5.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep5.Z.3o Ocamlary.Dep5.Z.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep6.3o Ocamlary.Dep6.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep6.X.3o Ocamlary.Dep6.X.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep6.X.Y.3o Ocamlary.Dep6.X.Y.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep7.3o Ocamlary.Dep7.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep7.M.3o Ocamlary.Dep7.M.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep8.3o Ocamlary.Dep8.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep9.3o Ocamlary.Dep9.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep11.3o Ocamlary.Dep11.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep12.3o Ocamlary.Dep12.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep13.3o Ocamlary.Dep13.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Dep13.c.3o Ocamlary.Dep13.c.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With2.3o Ocamlary.With2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With3.3o Ocamlary.With3.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With3.N.3o Ocamlary.With3.N.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With4.3o Ocamlary.With4.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With4.N.3o Ocamlary.With4.N.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With5.3o Ocamlary.With5.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With5.N.3o Ocamlary.With5.N.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With6.3o Ocamlary.With6.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With7.3o Ocamlary.With7.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With9.3o Ocamlary.With9.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.With10.3o Ocamlary.With10.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.DoubleInclude1.3o Ocamlary.DoubleInclude1.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.DoubleInclude1.DoubleInclude2.3o
+ Ocamlary.DoubleInclude1.DoubleInclude2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.DoubleInclude3.3o Ocamlary.DoubleInclude3.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.DoubleInclude3.DoubleInclude2.3o
+ Ocamlary.DoubleInclude3.DoubleInclude2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.IncludeInclude1.3o Ocamlary.IncludeInclude1.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.CanonicalTest.3o Ocamlary.CanonicalTest.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__List.3o
+ Ocamlary.CanonicalTest.Base__List.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__.3o
+ Ocamlary.CanonicalTest.Base__.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.CanonicalTest.Base.3o Ocamlary.CanonicalTest.Base.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base.List.3o
+ Ocamlary.CanonicalTest.Base.List.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__Tests.3o
+ Ocamlary.CanonicalTest.Base__Tests.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.Base__Tests.C.3o
+ Ocamlary.CanonicalTest.Base__Tests.C.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Ocamlary.CanonicalTest.List_modif.3o
+ Ocamlary.CanonicalTest.List_modif.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.3o Ocamlary.Aliases.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo__A.3o Ocamlary.Aliases.Foo__A.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo__B.3o Ocamlary.Aliases.Foo__B.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo__C.3o Ocamlary.Aliases.Foo__C.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo__D.3o Ocamlary.Aliases.Foo__D.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo__E.3o Ocamlary.Aliases.Foo__E.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo__.3o Ocamlary.Aliases.Foo__.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.3o Ocamlary.Aliases.Foo.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.A.3o Ocamlary.Aliases.Foo.A.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.B.3o Ocamlary.Aliases.Foo.B.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.C.3o Ocamlary.Aliases.Foo.C.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.D.3o Ocamlary.Aliases.Foo.D.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Foo.E.3o Ocamlary.Aliases.Foo.E.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.Std.3o Ocamlary.Aliases.Std.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.E.3o Ocamlary.Aliases.E.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.P1.3o Ocamlary.Aliases.P1.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.P1.Y.3o Ocamlary.Aliases.P1.Y.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Aliases.P2.3o Ocamlary.Aliases.P2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.M.3o Ocamlary.M.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Ocamlary.Only_a_module.3o Ocamlary.Only_a_module.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../section.odocl})
+ (with-stdout-to
+ Section.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Section.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Section.3o Section.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../stop.odocl})
+ (with-stdout-to
+ Stop.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Stop.3o'")))
+ (with-stdout-to
+ Stop.N.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Stop.N.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop.3o Stop.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop.N.3o Stop.N.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../stop_dead_link_doc.odocl})
+ (with-stdout-to
+ Stop_dead_link_doc.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Stop_dead_link_doc.3o'")))
+ (with-stdout-to
+ Stop_dead_link_doc.Foo.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Stop_dead_link_doc.Foo.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop_dead_link_doc.3o Stop_dead_link_doc.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Stop_dead_link_doc.Foo.3o Stop_dead_link_doc.Foo.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../toplevel_comments.odocl})
+ (with-stdout-to
+ Toplevel_comments.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.3o'")))
+ (with-stdout-to
+ Toplevel_comments.Include_inline.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.Include_inline.3o'")))
+ (with-stdout-to
+ Toplevel_comments.Include_inline'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.Include_inline'\\''.3o'")))
+ (with-stdout-to
+ Toplevel_comments.M.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.M.3o'")))
+ (with-stdout-to
+ Toplevel_comments.M'.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.M'\\''.3o'")))
+ (with-stdout-to
+ Toplevel_comments.M''.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.M'\\'''\\''.3o'")))
+ (with-stdout-to
+ Toplevel_comments.Alias.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.Alias.3o'")))
+ (with-stdout-to
+ Toplevel_comments.c1.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.c1.3o'")))
+ (with-stdout-to
+ Toplevel_comments.c2.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Toplevel_comments.c2.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.3o Toplevel_comments.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.Include_inline.3o
+ Toplevel_comments.Include_inline.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff
+ Toplevel_comments.Include_inline'.3o
+ Toplevel_comments.Include_inline'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.M.3o Toplevel_comments.M.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.M'.3o Toplevel_comments.M'.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.M''.3o Toplevel_comments.M''.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.Alias.3o Toplevel_comments.Alias.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.c1.3o Toplevel_comments.c1.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Toplevel_comments.c2.3o Toplevel_comments.c2.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../type.odocl})
+ (with-stdout-to
+ Type.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Type.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Type.3o Type.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
+
+(rule
+ (action
+ (progn
+ (run odoc man-generate -o man.gen %{dep:../val.odocl})
+ (with-stdout-to
+ Val.3o.gen
+ (progn
+ (system "cat 'man.gen/test/Val.3o'"))))))
+
+(rule
+ (alias runtest)
+ (action
+ (diff Val.3o Val.3o.gen))
+ (enabled_if
+ (>= %{ocaml_version} 4.10)))
diff --git a/test/man/expect/test_package+ml/mld.3o b/test/generators/cases_pre408/man/mld.3o
similarity index 97%
rename from test/man/expect/test_package+ml/mld.3o
rename to test/generators/cases_pre408/man/mld.3o
index b0b576b69d..4b8e7078c0 100644
--- a/test/man/expect/test_package+ml/mld.3o
+++ b/test/generators/cases_pre408/man/mld.3o
@@ -1,7 +1,7 @@
.TH mld 3 "" "Odoc" "OCaml Library"
.SH Name
-test_package+ml\.mld
+test\.mld
.SH Synopsis
.sp
.in 2
diff --git a/test/generators/dune b/test/generators/dune
new file mode 100644
index 0000000000..1e78bb4d50
--- /dev/null
+++ b/test/generators/dune
@@ -0,0 +1,34 @@
+(library
+ (name gen_link_lib)
+ (modules gen_link_lib)
+ (libraries sexplib0 gen_backend)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
+
+(library
+ (name gen_backend)
+ (modules gen_backend)
+ (libraries sexplib0 unix fpath)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
+
+(library
+ (name html_t_rule)
+ (modules html_t_rule)
+ (libraries sexplib0 gen_backend)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
+
+(library
+ (name latex_t_rule)
+ (modules latex_t_rule)
+ (libraries sexplib0 gen_backend)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
+
+(library
+ (name man_t_rule)
+ (modules man_t_rule)
+ (libraries sexplib0 gen_backend)
+ (enabled_if
+ (>= %{ocaml_version} 4.04)))
diff --git a/test/generators/gen_backend.ml b/test/generators/gen_backend.ml
new file mode 100644
index 0000000000..abbfc5dca6
--- /dev/null
+++ b/test/generators/gen_backend.ml
@@ -0,0 +1,88 @@
+type sexp = Sexplib0.Sexp.t = Atom of string | List of sexp list
+
+let read_lines ic =
+ let lines = ref [] in
+ try
+ while true do
+ lines := input_line ic :: !lines
+ done;
+ assert false
+ with End_of_file -> List.rev !lines
+
+let die s =
+ prerr_endline s;
+ exit 1
+
+let lines_of_command prog args =
+ let cmd = String.concat " " (prog :: List.map Filename.quote args) in
+ let inp = Unix.open_process_in cmd in
+ let lines = read_lines inp in
+ match Unix.close_process_in inp with
+ | Unix.WEXITED 0 -> lines
+ | _ -> die (cmd ^ " exited with non-zero status")
+
+let expected_targets backend odocl =
+ lines_of_command "odoc "
+ [ backend ^ "-targets"; "-o"; backend ^ ".gen"; Fpath.to_string odocl ]
+ |> List.map Fpath.v
+
+let tweak_target target =
+ match Fpath.segs target with
+ | _ :: _ :: rest -> String.concat "." rest
+ | _ -> assert false
+
+let gen_targets targets =
+ List.map
+ (fun t ->
+ List
+ [
+ Atom "with-stdout-to";
+ Atom (tweak_target t ^ ".gen");
+ List
+ [
+ Atom "progn";
+ List
+ [
+ Atom "system";
+ Atom ("cat " ^ Filename.quote (Fpath.to_string t));
+ ];
+ ];
+ ])
+ targets
+
+let diff_rule t ocaml_ver =
+ List
+ [
+ Atom "rule";
+ List [ Atom "alias"; Atom "runtest" ];
+ List
+ [
+ Atom "action";
+ List
+ [
+ Atom "diff";
+ Atom (Fpath.to_string t);
+ Atom (Fpath.to_string t ^ ".gen");
+ ];
+ ];
+ List
+ [
+ Atom "enabled_if";
+ List [ Atom ">="; Atom "%{ocaml_version}"; Atom ocaml_ver ];
+ ];
+ ]
+
+let diff_rules targets ocaml_ver =
+ List.map (fun t -> diff_rule t ocaml_ver) targets
+
+let gen_backend_rules backend target_rule filenames ocaml_ver =
+ let rules =
+ (List.map (fun odocl ->
+ let targets = expected_targets backend odocl in
+ let paths = List.map tweak_target targets |> List.map Fpath.v in
+ target_rule odocl targets :: diff_rules paths ocaml_ver))
+ filenames
+ in
+ List.flatten rules
+
+let files = List.tl (Array.to_list Sys.argv) |> List.map Fpath.v
diff --git a/test/generators/gen_link_lib.ml b/test/generators/gen_link_lib.ml
new file mode 100644
index 0000000000..8aca500180
--- /dev/null
+++ b/test/generators/gen_link_lib.ml
@@ -0,0 +1,267 @@
+type sexp = Sexplib0.Sexp.t = Atom of string | List of sexp list
+
+let cu_target_rule dep_path target_path =
+ List
+ [
+ Atom "rule";
+ List [ Atom "target"; Atom target_path ];
+ List [ Atom "deps"; Atom (Fpath.to_string dep_path) ];
+ List
+ [
+ Atom "action";
+ List
+ [
+ Atom "run";
+ Atom "ocamlc";
+ Atom "-c";
+ Atom "-bin-annot";
+ Atom "-o";
+ Atom "%{target}";
+ Atom "%{deps}";
+ ];
+ ];
+ ]
+
+let odoc_target_rule dep_path target_path =
+ List
+ [
+ Atom "rule";
+ List [ Atom "target"; Atom (Fpath.basename target_path) ];
+ List [ Atom "deps"; Atom (Fpath.basename dep_path) ];
+ List
+ [
+ Atom "action";
+ List
+ [
+ Atom "run";
+ Atom "odoc";
+ Atom "compile";
+ Atom "--pkg";
+ Atom "test";
+ Atom "-o";
+ Atom "%{target}";
+ Atom "%{deps}";
+ ];
+ ];
+ ]
+
+let odocl_target_rule dep_path target_path =
+ List
+ [
+ Atom "rule";
+ List [ Atom "target"; Atom (Fpath.basename target_path) ];
+ List [ Atom "deps"; Atom (Fpath.basename dep_path) ];
+ List
+ [
+ Atom "action";
+ List
+ [
+ Atom "run";
+ Atom "odoc";
+ Atom "link";
+ Atom "-o";
+ Atom "%{target}";
+ Atom "%{deps}";
+ ];
+ ];
+ ]
+
+let mld_odoc_target_rule dep_path target_path =
+ List
+ [
+ Atom "rule";
+ List [ Atom "target"; Atom (Fpath.basename target_path) ];
+ List [ Atom "deps"; Atom (Fpath.to_string dep_path) ];
+ List
+ [
+ Atom "action";
+ List
+ [
+ Atom "run";
+ Atom "odoc";
+ Atom "compile";
+ Atom "--pkg";
+ Atom "test";
+ Atom "-o";
+ Atom "%{target}";
+ Atom "%{deps}";
+ ];
+ ];
+ ]
+
+let set_odocl_ext = Fpath.set_ext ".odocl"
+
+let set_odoc_ext = Fpath.set_ext ".odoc"
+
+let file_rule path ext =
+ let cm_file = Fpath.set_ext ext path in
+ let odoc_file = set_odoc_ext path in
+ let odocl_file = set_odocl_ext path in
+ [
+ cu_target_rule path (Fpath.basename cm_file);
+ odoc_target_rule cm_file odoc_file;
+ odocl_target_rule odoc_file odocl_file;
+ ]
+
+let mld_file_rule path =
+ let path' = Fpath.(v ("page-" ^ basename path)) in
+ let odoc_file = set_odoc_ext path' in
+ let odocl_file = set_odocl_ext path' in
+ [
+ mld_odoc_target_rule path odoc_file; odocl_target_rule odoc_file odocl_file;
+ ]
+
+let die s =
+ prerr_endline s;
+ exit 1
+
+let path' () f = Filename.quote (Fpath.to_string f)
+
+let ext' () f = Filename.quote (Fpath.get_ext f)
+
+let cases = Fpath.v "cases"
+
+let is_dot_ocamlformat p = Fpath.filename p = ".ocamlformat"
+
+let gen_rule_for_source_file path =
+ let ext = Fpath.get_ext path in
+ match ext with
+ | ".ml" -> file_rule path ".cmt"
+ | ".mli" -> file_rule path ".cmti"
+ | ".mld" -> mld_file_rule path
+ | _ ->
+ die
+ (Printf.sprintf
+ "Don't know what to do with %a because of unrecognized %a extension."
+ path' path ext' path)
+
+let html, latex, man = ("html", "latex", "man")
+
+let dune_inc, dune_inc_gen, gen_, exe =
+ (".dune.inc", ".dune.inc.gen", "gen_", ".exe")
+
+type backend = {
+ subdir : Fpath.t;
+ dune_inc : string;
+ dune_inc_gen : string;
+ dune_inc' : string;
+ dune_inc_gen' : string;
+ gen_exe : string;
+}
+
+let html =
+ {
+ subdir = Fpath.v html;
+ dune_inc = html ^ dune_inc;
+ dune_inc_gen = html ^ dune_inc_gen;
+ dune_inc' = html ^ "/" ^ html ^ dune_inc;
+ dune_inc_gen' = html ^ "/" ^ html ^ dune_inc_gen;
+ gen_exe = gen_ ^ html ^ "/" ^ gen_ ^ html ^ exe;
+ }
+
+let latex =
+ {
+ subdir = Fpath.v latex;
+ dune_inc = latex ^ dune_inc;
+ dune_inc_gen = latex ^ dune_inc_gen;
+ dune_inc' = latex ^ "/" ^ latex ^ dune_inc;
+ dune_inc_gen' = latex ^ "/" ^ latex ^ dune_inc_gen;
+ gen_exe = gen_ ^ latex ^ "/" ^ gen_ ^ latex ^ exe;
+ }
+
+let man =
+ {
+ subdir = Fpath.v man;
+ dune_inc = man ^ dune_inc;
+ dune_inc_gen = man ^ dune_inc_gen;
+ dune_inc' = man ^ "/" ^ man ^ dune_inc;
+ dune_inc_gen' = man ^ "/" ^ man ^ dune_inc_gen;
+ gen_exe = gen_ ^ man ^ "/" ^ gen_ ^ man ^ exe;
+ }
+
+let backends = [ html; latex; man ]
+
+let dep_atom p = Atom (Printf.sprintf "%%{dep:%s}" (Fpath.to_string p))
+
+let odocls backend paths =
+ paths
+ |> List.map (fun p ->
+ let path = Fpath.relativize ~root:backend p in
+ match path with Some p -> dep_atom p | None -> assert false)
+
+let gen_backend_diff_rule paths =
+ List.map
+ (fun b ->
+ List
+ [
+ Atom "subdir";
+ Atom (Fpath.to_string b.subdir);
+ List
+ [
+ Atom "rule";
+ List
+ [
+ Atom "with-stdout-to";
+ Atom b.dune_inc_gen;
+ List
+ [
+ Atom "pipe-stdout";
+ List
+ (Atom "run" :: Atom b.gen_exe :: odocls b.subdir paths);
+ List [ Atom "run"; Atom "dune"; Atom "format-dune-file" ];
+ ];
+ ];
+ ];
+ ])
+ backends
+
+let diff_rules ocaml_ver =
+ List.map
+ (fun b ->
+ List
+ [
+ Atom "rule";
+ List [ Atom "alias"; Atom "runtest" ];
+ List
+ [
+ Atom "action";
+ List [ Atom "diff"; Atom b.dune_inc'; Atom b.dune_inc_gen' ];
+ ];
+ List
+ [
+ Atom "enabled_if";
+ List [ Atom ">="; Atom "%{ocaml_version}"; Atom ocaml_ver ];
+ ];
+ ])
+ backends
+
+let gen_backend_rule paths ocaml_ver =
+ [ gen_backend_diff_rule paths; diff_rules ocaml_ver ] |> List.flatten
+
+let read_file_from_dir dir =
+ let filenames =
+ let arr = Sys.readdir dir in
+ Array.sort String.compare arr;
+ Array.to_list arr
+ in
+ let dir = Fpath.v dir in
+ List.map (Fpath.( / ) dir) filenames
+
+let gen_rule paths ocaml_ver =
+ let paths' =
+ List.map
+ (fun p ->
+ let path = Fpath.relativize ~root:cases p in
+ match path with
+ | Some p ->
+ if Fpath.get_ext p = ".mld" then
+ set_odocl_ext Fpath.(parent p / ("page-" ^ filename p))
+ else set_odocl_ext Fpath.(parent p / filename p)
+ | None -> assert false)
+ paths
+ in
+ List.flatten
+ [
+ List.(flatten (map gen_rule_for_source_file paths));
+ gen_backend_rule paths' ocaml_ver;
+ ]
diff --git a/test/generators/html_t_rule.ml b/test/generators/html_t_rule.ml
new file mode 100644
index 0000000000..304215c690
--- /dev/null
+++ b/test/generators/html_t_rule.ml
@@ -0,0 +1,23 @@
+let html_target_rule odocl targets : Gen_backend.sexp =
+ List
+ [
+ Atom "rule";
+ List
+ [
+ Atom "action";
+ List
+ (Atom "progn"
+ ::
+ List
+ [
+ Atom "run";
+ Atom "odoc";
+ Atom "html-generate";
+ Atom "--indent";
+ Atom "-o";
+ Atom "html.gen";
+ Atom ("%{dep:" ^ Fpath.to_string odocl ^ "}");
+ ]
+ :: Gen_backend.gen_targets targets);
+ ];
+ ]
diff --git a/test/generators/latex_t_rule.ml b/test/generators/latex_t_rule.ml
new file mode 100644
index 0000000000..b3e7eda5cb
--- /dev/null
+++ b/test/generators/latex_t_rule.ml
@@ -0,0 +1,22 @@
+let latex_target_rule odocl targets : Gen_backend.sexp =
+ List
+ [
+ Atom "rule";
+ List
+ [
+ Atom "action";
+ List
+ (Atom "progn"
+ ::
+ List
+ [
+ Atom "run";
+ Atom "odoc";
+ Atom "latex-generate";
+ Atom "-o";
+ Atom "latex.gen";
+ Atom ("%{dep:" ^ Fpath.to_string odocl ^ "}");
+ ]
+ :: Gen_backend.gen_targets targets);
+ ];
+ ]
diff --git a/test/generators/man_t_rule.ml b/test/generators/man_t_rule.ml
new file mode 100644
index 0000000000..311d129f05
--- /dev/null
+++ b/test/generators/man_t_rule.ml
@@ -0,0 +1,22 @@
+let man_target_rule odocl targets : Gen_backend.sexp =
+ List
+ [
+ Atom "rule";
+ List
+ [
+ Atom "action";
+ List
+ (Atom "progn"
+ ::
+ List
+ [
+ Atom "run";
+ Atom "odoc";
+ Atom "man-generate";
+ Atom "-o";
+ Atom "man.gen";
+ Atom ("%{dep:" ^ Fpath.to_string odocl ^ "}");
+ ]
+ :: Gen_backend.gen_targets targets);
+ ];
+ ]
diff --git a/test/html/dune b/test/html/dune
deleted file mode 100644
index 9a72e3ed93..0000000000
--- a/test/html/dune
+++ /dev/null
@@ -1,13 +0,0 @@
-(executable
- (name test)
- (libraries alcotest markup))
-
-(rule
- (alias runtest)
- (action
- (run %{exe:test.exe}))
- (deps
- test.exe
- %{workspace_root}/src/odoc/bin/main.exe
- (source_tree ../cases)
- (source_tree expect)))
diff --git a/test/html/expect/README.md b/test/html/expect/README.md
deleted file mode 100644
index ed2485aae0..0000000000
--- a/test/html/expect/README.md
+++ /dev/null
@@ -1,3 +0,0 @@
-The symlink `odoc.css` in this directory is a silly hack that helps to display
-the HTML files in `test/html/cases/*` correctly: they expect `odoc.css` at
-relative path `../../odoc.css`. The same is true for `highlight.pack.js`.
diff --git a/test/html/expect/highlight.pack.js b/test/html/expect/highlight.pack.js
deleted file mode 120000
index 7b7b542659..0000000000
--- a/test/html/expect/highlight.pack.js
+++ /dev/null
@@ -1 +0,0 @@
-../../../src/vendor/highlight.pack.js
\ No newline at end of file
diff --git a/test/html/expect/odoc.css b/test/html/expect/odoc.css
deleted file mode 120000
index 95360cfe37..0000000000
--- a/test/html/expect/odoc.css
+++ /dev/null
@@ -1 +0,0 @@
-../../../src/odoc/etc/odoc.css
\ No newline at end of file
diff --git a/test/html/expect/test_package+custom_theme,ml/Include/index.html b/test/html/expect/test_package+custom_theme,ml/Include/index.html
deleted file mode 100644
index 33869d5ed5..0000000000
--- a/test/html/expect/test_package+custom_theme,ml/Include/index.html
+++ /dev/null
@@ -1,137 +0,0 @@
-
-
-
-
- Include (test_package+custom_theme,ml.Include)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+custom_theme,ml » Include
-
-
-
-
-
-
-
-
module type Inlined = sig ... end
-
-
-
-
-
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+custom_theme,ml/Include2/index.html b/test/html/expect/test_package+custom_theme,ml/Include2/index.html
deleted file mode 100644
index e69de29bb2..0000000000
diff --git a/test/html/expect/test_package+custom_theme,ml/Include_sections/index.html b/test/html/expect/test_package+custom_theme,ml/Include_sections/index.html
deleted file mode 100644
index e69de29bb2..0000000000
diff --git a/test/html/expect/test_package+custom_theme,ml/Include_sections/module-type-Something/index.html b/test/html/expect/test_package+custom_theme,ml/Include_sections/module-type-Something/index.html
deleted file mode 100644
index e69de29bb2..0000000000
diff --git a/test/html/expect/test_package+custom_theme,ml/Module/index.html b/test/html/expect/test_package+custom_theme,ml/Module/index.html
deleted file mode 100644
index a2968b9a1b..0000000000
--- a/test/html/expect/test_package+custom_theme,ml/Module/index.html
+++ /dev/null
@@ -1,111 +0,0 @@
-
-
-
-
- Module (test_package+custom_theme,ml.Module)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+custom_theme,ml » Module
-
-
-
- Module Module
-
-
- Foo.
-
-
-
-
-
-
-
module type S = sig ... end
-
-
-
-
-
-
-
module type S3 = S with type t = int and type u = string
-
-
-
-
-
module type S4 = S with type t := int
-
-
-
-
-
module type S5 = S with type 'a v := 'a list
-
-
-
-
-
-
module type S6 = S with type ('a, 'b) w := ('a , 'b ) result
-
-
-
-
-
module M' : sig ... end
-
-
-
-
-
module type S7 = S with module M = M'
-
-
-
-
-
module type S8 = S with module M := M'
-
-
-
-
-
module type S9 = module type of M'
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+custom_theme,ml/Section/index.html b/test/html/expect/test_package+custom_theme,ml/Section/index.html
deleted file mode 100644
index 99071883fe..0000000000
--- a/test/html/expect/test_package+custom_theme,ml/Section/index.html
+++ /dev/null
@@ -1,99 +0,0 @@
-
-
-
-
- Section (test_package+custom_theme,ml.Section)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+custom_theme,ml » Section
-
-
-
-
-
-
-
- Empty section
-
-
- Text only
-
-
- Foo bar.
-
-
- Aside only
-
-
- Foo bar.
-
-
- Value only
-
-
-
- Empty section
-
-
-
- and one with a nested section
-
-
- This section
title has markup
-
-
- But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link.
-
-
-
-
diff --git a/test/html/expect/test_package+custom_theme,ml/Val/index.html b/test/html/expect/test_package+custom_theme,ml/Val/index.html
deleted file mode 100644
index cffe59a264..0000000000
--- a/test/html/expect/test_package+custom_theme,ml/Val/index.html
+++ /dev/null
@@ -1,53 +0,0 @@
-
-
-
-
- Val (test_package+custom_theme,ml.Val)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+custom_theme,ml » Val
-
-
-
-
-
-
val documented : unit
-
-
-
-
-
-
val undocumented : unit
-
-
-
-
-
val documented_above : unit
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Alias/X/index.html b/test/html/expect/test_package+ml/Alias/X/index.html
deleted file mode 100644
index 9de66487da..0000000000
--- a/test/html/expect/test_package+ml/Alias/X/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- X (test_package+ml.Alias.X)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Alias » X
-
-
-
-
-
-
-
- Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X'
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Alias/index.html b/test/html/expect/test_package+ml/Alias/index.html
deleted file mode 100644
index 370cc90eb2..0000000000
--- a/test/html/expect/test_package+ml/Alias/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- Alias (test_package+ml.Alias)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Alias
-
-
-
-
-
-
module Foo__X : sig ... end
-
-
-
-
-
module X : sig ... end
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Bugs/index.html b/test/html/expect/test_package+ml/Bugs/index.html
deleted file mode 100644
index d03c639df1..0000000000
--- a/test/html/expect/test_package+ml/Bugs/index.html
+++ /dev/null
@@ -1,43 +0,0 @@
-
-
-
-
- Bugs (test_package+ml.Bugs)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Bugs
-
-
-
-
-
-
type 'a opt = 'a option
-
-
-
-
-
val foo : ?bar:'a -> unit -> unit
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Bugs_post_406/index.html b/test/html/expect/test_package+ml/Bugs_post_406/index.html
deleted file mode 100644
index 4dfbde186b..0000000000
--- a/test/html/expect/test_package+ml/Bugs_post_406/index.html
+++ /dev/null
@@ -1,41 +0,0 @@
-
-
-
-
- Bugs_post_406 (test_package+ml.Bugs_post_406)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Bugs_post_406
-
-
-
-
-
-
class type let_open = object ... end
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Bugs_pre_410/index.html b/test/html/expect/test_package+ml/Bugs_pre_410/index.html
deleted file mode 100644
index 4c95e2bfba..0000000000
--- a/test/html/expect/test_package+ml/Bugs_pre_410/index.html
+++ /dev/null
@@ -1,43 +0,0 @@
-
-
-
-
- Bugs_pre_410 (test_package+ml.Bugs_pre_410)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Bugs_pre_410
-
-
-
- Module Bugs_pre_410
-
-
-
-
-
-
type 'a opt' = int option
-
-
-
-
-
val foo' : ?bar:'a -> unit -> unit
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Class/index.html b/test/html/expect/test_package+ml/Class/index.html
deleted file mode 100644
index ea892bdaa9..0000000000
--- a/test/html/expect/test_package+ml/Class/index.html
+++ /dev/null
@@ -1,73 +0,0 @@
-
-
-
-
- Class (test_package+ml.Class)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Class
-
-
-
-
-
-
class type empty = object ... end
-
-
-
-
-
class type mutually = object ... end
-
-
-
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/External/index.html b/test/html/expect/test_package+ml/External/index.html
deleted file mode 100644
index 60a139cdbc..0000000000
--- a/test/html/expect/test_package+ml/External/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- External (test_package+ml.External)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » External
-
-
-
-
-
-
val foo : unit -> unit
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Functor/index.html b/test/html/expect/test_package+ml/Functor/index.html
deleted file mode 100644
index 3f5935f285..0000000000
--- a/test/html/expect/test_package+ml/Functor/index.html
+++ /dev/null
@@ -1,63 +0,0 @@
-
-
-
-
- Functor (test_package+ml.Functor)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Functor
-
-
-
-
-
-
module type S = sig ... end
-
-
-
-
-
module type S1 = functor (_ : S ) -> S
-
-
-
-
-
-
-
module F3 (Arg : S ) : sig ... end
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Include/index.html b/test/html/expect/test_package+ml/Include/index.html
deleted file mode 100644
index c6de2f9505..0000000000
--- a/test/html/expect/test_package+ml/Include/index.html
+++ /dev/null
@@ -1,137 +0,0 @@
-
-
-
-
- Include (test_package+ml.Include)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Include
-
-
-
-
-
-
-
-
module type Inlined = sig ... end
-
-
-
-
-
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Include2/Y_include_doc/index.html b/test/html/expect/test_package+ml/Include2/Y_include_doc/index.html
deleted file mode 100644
index 5dfaf3370b..0000000000
--- a/test/html/expect/test_package+ml/Include2/Y_include_doc/index.html
+++ /dev/null
@@ -1,45 +0,0 @@
-
-
-
-
- Y_include_doc (test_package+ml.Include2.Y_include_doc)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Include2 » Y_include_doc
-
-
-
- Module Include2.Y_include_doc
-
-
-
-
-
-
- Doc attached to include Y
. Y
's top-comment shouldn't appear here.
-
-
-
-
- include module type of struct include Y end
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Include2/Y_include_synopsis/index.html b/test/html/expect/test_package+ml/Include2/Y_include_synopsis/index.html
deleted file mode 100644
index ba5ffa2601..0000000000
--- a/test/html/expect/test_package+ml/Include2/Y_include_synopsis/index.html
+++ /dev/null
@@ -1,43 +0,0 @@
-
-
-
-
- Y_include_synopsis (test_package+ml.Include2.Y_include_synopsis)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Include2 » Y_include_synopsis
-
-
-
-
-
-
- include module type of struct include Y end
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Include2/index.html b/test/html/expect/test_package+ml/Include2/index.html
deleted file mode 100644
index ac6698150a..0000000000
--- a/test/html/expect/test_package+ml/Include2/index.html
+++ /dev/null
@@ -1,78 +0,0 @@
-
-
-
-
- Include2 (test_package+ml.Include2)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Include2
-
-
-
-
-
-
module X : sig ... end
-
-
-
- Comment about X that should not appear when including X below.
-
-
-
-
-
-
- include module type of struct include X end
-
-
- Comment about X that should not appear when including X below.
-
-
-
-
-
-
-
module Y : sig ... end
-
-
-
- Top-comment of Y.
-
-
-
-
-
-
-
- The include Y
below should have the synopsis from Y
's top-comment attached to it.
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Include_sections/index.html b/test/html/expect/test_package+ml/Include_sections/index.html
deleted file mode 100644
index adeaa7e7b0..0000000000
--- a/test/html/expect/test_package+ml/Include_sections/index.html
+++ /dev/null
@@ -1,256 +0,0 @@
-
-
-
-
- Include_sections (test_package+ml.Include_sections)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Include_sections
-
-
-
- Module Include_sections
-
-
-
-
-
-
-
-
- Let's include Something
once
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
- Second include
-
-
- Let's include Something
a second time: the heading level should be shift here.
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
- Third include
-
-
- Shifted some more.
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
- And let's include it again, but without inlining it this time: the ToC shouldn't grow.
-
-
-
-
- include Something
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Include_sections/module-type-Something/index.html b/test/html/expect/test_package+ml/Include_sections/module-type-Something/index.html
deleted file mode 100644
index 0b98e45897..0000000000
--- a/test/html/expect/test_package+ml/Include_sections/module-type-Something/index.html
+++ /dev/null
@@ -1,81 +0,0 @@
-
-
-
-
- Something (test_package+ml.Include_sections.Something)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Include_sections » Something
-
-
-
- Module type Include_sections.Something
-
-
- A module type.
-
-
-
-
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Interlude/index.html b/test/html/expect/test_package+ml/Interlude/index.html
deleted file mode 100644
index 0d62f6863b..0000000000
--- a/test/html/expect/test_package+ml/Interlude/index.html
+++ /dev/null
@@ -1,81 +0,0 @@
-
-
-
-
- Interlude (test_package+ml.Interlude)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Interlude
-
-
-
-
- Some separate stray text at the top of the module.
-
-
-
- Some stray text that is not associated with any signature item.
-
-
- It has multiple paragraphs.
-
-
- A separate block of stray text, adjacent to the preceding one.
-
-
-
-
-
-
- Stray text at the bottom of the module.
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Labels/index.html b/test/html/expect/test_package+ml/Labels/index.html
deleted file mode 100644
index 684fad6386..0000000000
--- a/test/html/expect/test_package+ml/Labels/index.html
+++ /dev/null
@@ -1,235 +0,0 @@
-
-
-
-
- Labels (test_package+ml.Labels)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Labels
-
-
-
-
-
-
-
- Attached to unit
-
-
- Attached to nothing
-
-
-
-
module A : sig ... end
-
-
-
-
-
-
-
- Attached to value
-
-
-
-
-
-
-
- Attached to external
-
-
-
-
-
-
module type S = sig ... end
-
-
-
-
-
class c : object ... end
-
-
-
-
-
class type cs = object ... end
-
-
-
-
-
-
- Attached to exception
-
-
-
-
-
-
-
-
- Attached to extension
-
-
-
-
-
-
-
- Attached to module subst
-
-
-
-
-
-
-
- Attached to type subst
-
-
-
-
-
-
type u =
-
-
-
-
- | A'
-
-
-
-
- Attached to constructor
-
-
-
-
-
-
-
-
-
-
-
type v = {
-
-
-
-
- f : t ;
-
-
-
-
- Attached to field
-
-
-
-
-
-
-
}
-
-
-
- Testing that labels can be referenced
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Markup/index.html b/test/html/expect/test_package+ml/Markup/index.html
deleted file mode 100644
index a4712ed417..0000000000
--- a/test/html/expect/test_package+ml/Markup/index.html
+++ /dev/null
@@ -1,378 +0,0 @@
-
-
-
-
- Markup (test_package+ml.Markup)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Markup
-
-
-
-
-
-
-
- Sections
-
-
- Let's get these done first, because sections will be used to break up the rest of this test.
-
-
- Besides the section heading above, there are also
-
-
- Subsection headings
-
-
- and
-
-
- Sub-subsection headings
-
-
- but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files.
-
-
- Anchors
-
-
- Sections can have attached Anchors , and it is possible to link to them. Links to section headers should not be set in source code style.
-
-
- Paragraph
-
-
- Individual paragraphs can have a heading.
-
-
- Subparagraph
-
-
- Parts of a longer paragraph that can be considered alone can also have headings.
-
-
- Styling
-
-
- This paragraph has some styled elements: bold and italic , bold italic , emphasis , emphasis within emphasis , bold italic , superscript , subscript . The line spacing should be enough for superscripts and subscripts not to look odd.
-
-
- Note: In italics emphasis is rendered as normal text while emphasis in emphasis is rendered in italics. It also work the same in links in italics with emphasis in emphasis .
-
-
- code
is a different kind of markup that doesn't allow nested markup.
-
-
- It's possible for two markup elements to appear next to each other and have a space, and appear next to each other with no space. It doesn't matter how much space it was in the source: in this sentence, it was two space characters. And in this one, there is a newline .
-
-
- This is also true between non- code
markup and code
.
-
-
- Code can appear inside other
markup . Its display shouldn't be affected.
-
-
- Links and references
-
-
- This is a link . It sends you to the top of this page. Links can have markup inside them: bold , italics , emphasis , superscript , subscript , and code
. Links can also be nested inside markup. Links cannot be nested inside each other. This link has no replacement text: # . The text is filled in by odoc. This is a shorthand link: # . The text is also filled in by odoc in this case.
-
-
- This is a reference to foo
. References can have replacement text: the value foo . Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: bold , italic , emphasis , superscript , subscript , and code
. It's also possible to surround a reference in a style: foo
. References can't be nested inside references, and links and references can't be nested inside each other.
-
-
- Preformatted text
-
-
- This is a code block:
-
-
let foo = ()
-(** There are some nested comments in here, but an unpaired comment
- terminator would terminate the whole doc surrounding comment. It's
- best to keep code blocks no wider than 72 characters. *)
-
-let bar =
- ignore foo
-
- There are also verbatim blocks:
-
-
The main difference is these don't get syntax highlighting.
-
- Lists
-
-
-
- This is a
-
-
- shorthand bulleted list,
-
-
- and the paragraphs in each list item support styling .
-
-
-
-
- This is a
-
-
- shorthand numbered list.
-
-
-
-
- Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break
-
-
-
- just creates a paragraph outside the list.
-
-
-
- Similarly, inserting a blank line between two list items
-
-
-
-
- creates two separate lists.
-
-
-
-
-
- but there is also the numbered variant.
-
-
-
-
-
-
- lists
-
-
- can be nested
-
-
- and can include references
-
-
- foo
-
-
-
-
-
- Unicode
-
-
- The parser supports any ASCII-compatible encoding, in particuλar UTF-8.
-
-
- Raw HTML
-
-
- Raw HTML can be as inline elements into sentences.
-
-
- If the raw HTML is the only thing in a paragraph, it is treated as a block
- element, and won't be wrapped in paragraph tags by the HTML generator.
-
-
- Modules
-
-
-
-
-
- X
-
-
- Y
-
-
- Z
-
-
-
-
- Each comment can end with zero or more tags. Here are some examples:
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- Comments in structure items support markup , to o .
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Module/index.html b/test/html/expect/test_package+ml/Module/index.html
deleted file mode 100644
index 680bf1268a..0000000000
--- a/test/html/expect/test_package+ml/Module/index.html
+++ /dev/null
@@ -1,111 +0,0 @@
-
-
-
-
- Module (test_package+ml.Module)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Module
-
-
-
- Module Module
-
-
- Foo.
-
-
-
-
-
-
-
module type S = sig ... end
-
-
-
-
-
-
-
module type S3 = S with type t = int and type u = string
-
-
-
-
-
module type S4 = S with type t := int
-
-
-
-
-
module type S5 = S with type 'a v := 'a list
-
-
-
-
-
-
module type S6 = S with type ('a, 'b) w := ('a , 'b ) result
-
-
-
-
-
module M' : sig ... end
-
-
-
-
-
module type S7 = S with module M = M'
-
-
-
-
-
module type S8 = S with module M := M'
-
-
-
-
-
module type S9 = module type of M'
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/F/argument-1-Arg1/index.html b/test/html/expect/test_package+ml/Nested/F/argument-1-Arg1/index.html
deleted file mode 100644
index 9e7bffbbe2..0000000000
--- a/test/html/expect/test_package+ml/Nested/F/argument-1-Arg1/index.html
+++ /dev/null
@@ -1,64 +0,0 @@
-
-
-
-
- Arg1 (test_package+ml.Nested.F.1-Arg1)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » F » 1-Arg1
-
-
-
- Parameter F.1-Arg1
-
-
-
-
-
-
-
- Type
-
-
-
- Values
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/F/argument-2-Arg2/index.html b/test/html/expect/test_package+ml/Nested/F/argument-2-Arg2/index.html
deleted file mode 100644
index 4008b523e9..0000000000
--- a/test/html/expect/test_package+ml/Nested/F/argument-2-Arg2/index.html
+++ /dev/null
@@ -1,48 +0,0 @@
-
-
-
-
- Arg2 (test_package+ml.Nested.F.2-Arg2)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » F » 2-Arg2
-
-
-
- Parameter F.2-Arg2
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/F/index.html b/test/html/expect/test_package+ml/Nested/F/index.html
deleted file mode 100644
index b3b0c97c76..0000000000
--- a/test/html/expect/test_package+ml/Nested/F/index.html
+++ /dev/null
@@ -1,76 +0,0 @@
-
-
-
-
- F (test_package+ml.Nested.F)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » F
-
-
-
-
-
-
-
- Type
-
-
- Parameters
-
-
-
-
-
module Arg2 : sig ... end
-
-
-
- Signature
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/X/index.html b/test/html/expect/test_package+ml/Nested/X/index.html
deleted file mode 100644
index df6ca4298e..0000000000
--- a/test/html/expect/test_package+ml/Nested/X/index.html
+++ /dev/null
@@ -1,70 +0,0 @@
-
-
-
-
- X (test_package+ml.Nested.X)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » X
-
-
-
-
-
-
-
- Type
-
-
-
- Values
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/class-inherits/index.html b/test/html/expect/test_package+ml/Nested/class-inherits/index.html
deleted file mode 100644
index c608eb9a99..0000000000
--- a/test/html/expect/test_package+ml/Nested/class-inherits/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- inherits (test_package+ml.Nested.inherits)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » inherits
-
-
-
- Class Nested.inherits
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/class-z/index.html b/test/html/expect/test_package+ml/Nested/class-z/index.html
deleted file mode 100644
index 8b72b2ee00..0000000000
--- a/test/html/expect/test_package+ml/Nested/class-z/index.html
+++ /dev/null
@@ -1,74 +0,0 @@
-
-
-
-
- z (test_package+ml.Nested.z)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » z
-
-
-
-
-
-
-
-
-
-
val mutable virtual y' : int
-
-
-
- Methods
-
-
-
-
-
method private virtual z' : int
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/index.html b/test/html/expect/test_package+ml/Nested/index.html
deleted file mode 100644
index 93ee8a7872..0000000000
--- a/test/html/expect/test_package+ml/Nested/index.html
+++ /dev/null
@@ -1,104 +0,0 @@
-
-
-
-
- Nested (test_package+ml.Nested)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested
-
-
-
-
-
-
-
- Module
-
-
-
-
module X : sig ... end
-
-
-
- This is module X.
-
-
-
-
- Module type
-
-
-
-
module type Y = sig ... end
-
-
-
- This is module type Y.
-
-
-
-
- Functor
-
-
-
-
module F (Arg1 : Y ) (Arg2 : sig ... end ) : sig ... end
-
-
-
- This is a functor F.
-
-
-
-
- Class
-
-
-
-
class virtual z : object ... end
-
-
-
-
-
-
class virtual inherits : object ... end
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Nested/module-type-Y/index.html b/test/html/expect/test_package+ml/Nested/module-type-Y/index.html
deleted file mode 100644
index fcdedd739e..0000000000
--- a/test/html/expect/test_package+ml/Nested/module-type-Y/index.html
+++ /dev/null
@@ -1,70 +0,0 @@
-
-
-
-
- Y (test_package+ml.Nested.Y)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Nested » Y
-
-
-
-
-
-
-
- Type
-
-
-
- Values
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Ocamlary/index.html b/test/html/expect/test_package+ml/Ocamlary/index.html
deleted file mode 100644
index 32400bf941..0000000000
--- a/test/html/expect/test_package+ml/Ocamlary/index.html
+++ /dev/null
@@ -1,2019 +0,0 @@
-
-
-
-
- Ocamlary (test_package+ml.Ocamlary)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Ocamlary
-
-
-
- Module Ocamlary
-
-
- This is an interface with all of the module system features. This documentation demonstrates:
-
-
-
- A numbered list:
-
-
-
- 3
-
-
- 2
-
-
- 1
-
-
-
- David Sheets is the author.
-
-
-
-
-
-
-
-
- You may find more information about this HTML documentation renderer at github.com/dsheets/ocamlary .
-
-
- This is some verbatim text:
-
-
verbatim
-
- This is some verbatim text:
-
-
[][df[]]}}
-
- Here is some raw LaTeX:
-
-
- Here is an index table of Empty
modules:
-
-
-
- Empty
A plain, empty module
-
-
- EmptyAlias
A plain module alias of Empty
-
-
-
- Here is a table of links to indexes: indexlist
-
-
- Here is some superscript: x2
-
-
- Here is some subscript: x0
-
-
- Here are some escaped brackets: { [ @ ] }
-
-
- Here is some emphasis followed by code
.
-
-
- An unassociated comment
-
-
- Level 1
-
-
- Level 2
-
-
- Level 3
-
-
- Level 4
-
-
- Basic module stuff
-
-
-
-
module Empty : sig ... end
-
-
-
- A plain, empty module
-
-
-
-
-
-
module type Empty = sig ... end
-
-
-
- An ambiguous, misnamed module type
-
-
-
-
-
-
-
- An ambiguous, misnamed module type
-
-
-
-
- Section 9000
-
-
-
-
module EmptyAlias = Empty
-
-
-
- A plain module alias of Empty
-
-
-
-
- EmptySig
-
-
-
-
-
- A plain, empty module signature
-
-
-
-
-
-
-
- A plain, empty module signature alias of
-
-
-
-
-
-
-
- A plain module of a signature of EmptySig
(reference)
-
-
-
-
-
-
-
- A plain module with an alias signature
-
-
-
-
-
-
module One : sig ... end
-
-
-
-
-
-
- There's a signature in a module in this signature.
-
-
-
-
-
- For a good time, see SuperSig
.SubSigA.subSig or SuperSig
.SubSigB.subSig or SuperSig.EmptySig
. Section Section 9000 is also interesting. EmptySig is the section and EmptySig
is the module signature.
-
-
-
-
module Buffer : sig ... end
-
-
-
-
- Some text before exception title.
-
-
- Basic exception stuff
-
-
- After exception title.
-
-
-
-
exception Kaboom of unit
-
-
-
- Unary exception constructor
-
-
-
-
-
-
exception Kablam of unit * unit
-
-
-
- Binary exception constructor
-
-
-
-
-
-
exception Kapow of unit * unit
-
-
-
- Unary exception constructor over binary tuple
-
-
-
-
-
-
-
exception EmptySigAlias
-
-
-
-
-
-
-
type ('a, 'b) a_function = 'a -> 'b
-
-
-
-
-
-
val a_function : x:int -> int
-
-
-
- This is a_function
with param and return type.
-
-
-
-
-
-
-
-
-
val fun_maybe : ?yes:unit -> unit -> int
-
-
-
-
-
val not_found : unit -> unit
-
-
-
-
-
-
val ocaml_org : string
-
-
-
-
-
-
val some_file : string
-
-
-
-
-
-
val some_doc : string
-
-
-
-
-
-
val since_mesozoic : unit
-
-
-
- This value was introduced in the Mesozoic era.
-
-
-
-
-
-
-
-
- This value has had changes in 1.0.0, 1.1.0, and 1.2.0.
-
-
-
-
-
-
-
- Some Operators
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- Advanced Module Stuff
-
-
-
-
-
- This comment is for CollectionModule
.
-
-
-
-
-
-
-
-
module type MMM = sig ... end
-
-
-
-
-
-
-
module type A = sig ... end
-
-
-
-
-
module type B = sig ... end
-
-
-
-
-
module type C = sig ... end
-
-
-
- This module type includes two signatures.
-
-
-
-
-
-
-
- This comment is for FunctorTypeOf
.
-
-
-
-
-
-
-
- This comment is for IncludeModuleType
.
-
-
-
-
-
-
- Advanced Type Stuff
-
-
-
-
type record = {
-
-
-
-
- field1 : int;
-
-
-
-
- This comment is for field1
.
-
-
-
-
-
-
- field2 : int;
-
-
-
-
- This comment is for field2
.
-
-
-
-
-
-
-
}
-
-
-
- This comment is for record
.
-
-
- This comment is also for record
.
-
-
-
-
-
-
type mutable_record = {
-
-
-
-
- mutable a : int;
-
-
-
-
- a
is first and mutable
-
-
-
-
-
-
- b : unit;
-
-
-
-
- b
is second and immutable
-
-
-
-
-
-
- mutable c : int;
-
-
-
-
- c
is third and mutable
-
-
-
-
-
-
-
}
-
-
-
-
-
type universe_record = {
-
-
-
-
- nihilate : a. 'a -> unit;
-
-
-
-
-
}
-
-
-
-
-
type variant =
-
-
-
-
- | TagA
-
-
-
-
- This comment is for TagA
.
-
-
-
-
-
-
- | ConstrB of int
-
-
-
-
- This comment is for ConstrB
.
-
-
-
-
-
-
- | ConstrC of int * int
-
-
-
-
- This comment is for binary ConstrC
.
-
-
-
-
-
-
- | ConstrD of int * int
-
-
-
-
- This comment is for unary ConstrD
of binary tuple.
-
-
-
-
-
-
-
-
-
- This comment is for variant
.
-
-
- This comment is also for variant
.
-
-
-
-
-
-
type poly_variant = [
-
-
-
-
- |
`TagA
-
-
-
-
- |
`ConstrB of int
-
-
-
-
-
]
-
-
-
- This comment is for poly_variant
.
-
-
- Wow! It was a polymorphic variant!
-
-
-
-
-
-
type (_, _) full_gadt =
-
-
-
-
- | Tag : (unit, unit) full_gadt
-
-
-
-
- | First : 'a -> ('a , unit) full_gadt
-
-
-
-
- | Second : 'a -> (unit, 'a ) full_gadt
-
-
-
-
- | Exist : 'a * 'b -> ('b , unit) full_gadt
-
-
-
-
-
-
-
- This comment is for full_gadt
.
-
-
- Wow! It was a GADT!
-
-
-
-
-
-
type 'a partial_gadt =
-
-
-
-
- This comment is for partial_gadt
.
-
-
- Wow! It was a mixed GADT!
-
-
-
-
-
-
-
- This comment is for alias
.
-
-
-
-
-
-
-
- This comment is for tuple
.
-
-
-
-
-
-
type variant_alias = variant =
-
-
-
-
- | TagA
-
-
-
-
- | ConstrB of int
-
-
-
-
- | ConstrC of int * int
-
-
-
-
- | ConstrD of int * int
-
-
-
-
-
-
-
- This comment is for variant_alias
.
-
-
-
-
-
-
type record_alias = record = {
-
-
-
-
- field1 : int;
-
-
-
-
- field2 : int;
-
-
-
-
-
}
-
-
-
- This comment is for record_alias
.
-
-
-
-
-
-
type poly_variant_union = [
-
-
]
-
-
-
- This comment is for poly_variant_union
.
-
-
-
-
-
-
type 'a poly_poly_variant = [
-
-
-
-
- |
`TagA of 'a
-
-
-
-
-
]
-
-
-
-
-
type ('a, 'b) bin_poly_poly_variant = [
-
-
-
-
- |
`TagA of 'a
-
-
-
-
- |
`ConstrB of 'b
-
-
-
-
-
]
-
-
-
-
-
type 'a open_poly_variant = [> `TagA ] as 'a
-
-
-
-
-
type 'a open_poly_variant2 = [> `ConstrB of int ] as 'a
-
-
-
-
-
-
type 'a poly_fun = [> `ConstrB of int ] as 'a -> 'a
-
-
-
-
-
type 'a poly_fun_constraint = 'a -> 'a constraint 'a = [> `TagA ]
-
-
-
-
-
type 'a closed_poly_variant = [< `One | `Two ] as 'a
-
-
-
-
-
type 'a clopen_poly_variant = [< `One | `Two of int | `Three Two Three ] as 'a
-
-
-
-
-
type nested_poly_variant = [
-
-
-
-
- |
`A
-
-
-
-
- |
`B of [ `B1 | `B2 ]
-
-
-
-
- |
`C
-
-
-
-
- |
`D of [ `D1 of [ `D1a ] ]
-
-
-
-
-
]
-
-
-
-
-
type ('a, 'b) full_gadt_alias = ('a , 'b ) full_gadt =
-
-
-
-
- This comment is for full_gadt_alias
.
-
-
-
-
-
-
-
- This comment is for partial_gadt_alias
.
-
-
-
-
-
-
exception Exn_arrow : unit -> exn
-
-
-
-
-
-
type mutual_constr_a =
-
-
-
-
-
-
-
and mutual_constr_b =
-
-
-
-
- | B
-
-
-
-
- | A_ish of mutual_constr_a
-
-
-
-
- This comment must be here for the next to associate correctly.
-
-
-
-
-
-
-
-
-
-
-
-
type rec_obj = < f : int; g : unit -> unit; h : rec_obj ; >
-
-
-
-
-
type 'a open_obj = < f : int; g : unit -> unit; .. > as 'a
-
-
-
-
-
type 'a oof = < a : unit; .. > as 'a -> 'a
-
-
-
-
-
type 'a any_obj = < .. > as 'a
-
-
-
-
-
-
type one_meth = < meth : unit; >
-
-
-
-
-
-
- A mystery wrapped in an ellipsis
-
-
-
-
-
-
-
-
type ext +=
-
-
-
-
- | ExtC of unit
-
-
-
-
- | ExtD of ext
-
-
-
-
-
-
-
-
-
-
-
type 'a poly_ext = ..
-
-
-
-
-
-
type poly_ext +=
-
-
-
-
- | Foo of 'b
-
-
-
-
- | Bar of 'b * 'b
-
-
-
-
- 'b poly_ext
-
-
-
-
-
-
-
-
-
-
-
type poly_ext +=
-
-
-
-
- | Quux of 'c
-
-
-
-
- 'c poly_ext
-
-
-
-
-
-
-
-
-
-
-
module ExtMod : sig ... end
-
-
-
-
-
type ExtMod.t +=
-
-
-
-
- | ZzzTop0
-
-
-
-
- It's got the rock
-
-
-
-
-
-
-
-
-
-
-
type ExtMod.t +=
-
-
-
-
- | ZzzTop of unit
-
-
-
-
- and it packs a unit.
-
-
-
-
-
-
-
-
-
-
-
val launch_missiles : unit -> unit
-
-
-
- Rotate keys on my mark...
-
-
-
-
-
-
-
- A brown paper package tied up with string
-
-
-
-
-
-
-
-
-
-
-
type 'a my_unit_class = unit param_class as 'a
-
-
-
-
-
module Dep1 : sig ... end
-
-
-
-
-
module Dep2 (Arg : sig ... end ) : sig ... end
-
-
-
-
-
-
module Dep3 : sig ... end
-
-
-
-
-
module Dep4 : sig ... end
-
-
-
-
-
module Dep5 (Arg : sig ... end ) : sig ... end
-
-
-
-
-
-
-
module Dep6 : sig ... end
-
-
-
-
-
module Dep7 (Arg : sig ... end ) : sig ... end
-
-
-
-
-
-
module Dep8 : sig ... end
-
-
-
-
-
module Dep9 (X : sig ... end ) : sig ... end
-
-
-
-
-
-
module Dep11 : sig ... end
-
-
-
-
-
module Dep12 (Arg : sig ... end ) : sig ... end
-
-
-
-
-
-
-
module type With1 = sig ... end
-
-
-
-
-
module With2 : sig ... end
-
-
-
-
-
-
-
-
-
module With5 : sig ... end
-
-
-
-
-
module With6 : sig ... end
-
-
-
-
-
module With7 (X : sig ... end ) : sig ... end
-
-
-
-
-
-
module With9 : sig ... end
-
-
-
-
-
module With10 : sig ... end
-
-
-
-
-
-
-
-
-
-
-
-
-
- Trying the {!modules: ...} command.
-
-
- With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references.
-
-
- With odoc, everything should be resolved (and linked) but only toplevel units will be documented.
-
-
-
- Weirder usages involving module types
-
-
-
- IncludeInclude1
.IncludeInclude2
-
-
- Dep4
.T
-
-
- A.Q
-
-
-
- Playing with @canonical paths
-
-
-
-
- Aliases again
-
-
-
-
-
- Let's imitate jst's layout.
-
-
-
-
- Section title splicing
-
-
- I can refer to
-
-
-
- But also to things in submodules:
-
-
-
- {!section:SuperSig.SubSigA.subSig}
: SuperSig
.SubSigA.subSig
-
-
- {!Aliases.incl}
: Aliases:incl
-
-
-
- And just to make sure we do not mess up:
-
-
-
- {{!section:indexmodules}A}
: A
-
-
- {{!aliases}B}
: B
-
-
- {{!section:SuperSig.SubSigA.subSig}C}
: C
-
-
- {{!Aliases.incl}D}
: D
-
-
-
- New reference syntax
-
-
-
-
module type M = sig ... end
-
-
-
-
-
module M : sig ... end
-
-
-
- Here goes:
-
-
-
- {!module-M.t}
: M.t
-
-
- {!module-type-M.t}
: M.t
-
-
-
-
- Some here should fail:
-
-
-
- {!Only_a_module.t}
: Only_a_module.t
-
-
- {!module-Only_a_module.t}
: Only_a_module.t
-
-
- {!module-type-Only_a_module.t}
: Only_a_module
.t : test
-
-
-
-
-
module type TypeExt = sig ... end
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Recent/X/index.html b/test/html/expect/test_package+ml/Recent/X/index.html
deleted file mode 100644
index 49a829d27c..0000000000
--- a/test/html/expect/test_package+ml/Recent/X/index.html
+++ /dev/null
@@ -1,48 +0,0 @@
-
-
-
-
- X (test_package+ml.Recent.X)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Recent » X
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Recent/index.html b/test/html/expect/test_package+ml/Recent/index.html
deleted file mode 100644
index fbd5d2bb49..0000000000
--- a/test/html/expect/test_package+ml/Recent/index.html
+++ /dev/null
@@ -1,244 +0,0 @@
-
-
-
-
- Recent (test_package+ml.Recent)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Recent
-
-
-
-
-
-
module type S = sig ... end
-
-
-
-
-
module type S1 = functor (_ : S ) -> S
-
-
-
-
-
type variant =
-
-
-
-
- | A
-
-
-
-
- | B of int
-
-
-
-
- | C
-
-
-
-
- foo
-
-
-
-
-
-
- | D
-
-
-
-
- bar
-
-
-
-
-
-
- | E of {
-
- }
-
-
-
-
-
-
-
-
-
type _ gadt =
-
-
-
-
- | A : int gadt
-
-
-
-
- | B : int -> string gadt
-
-
-
-
- foo
-
-
-
-
-
-
- | C : {
-
- } -> unit gadt
-
-
-
-
-
-
-
-
-
type polymorphic_variant = [
-
-
-
-
- |
`A
-
-
-
-
- |
`B of int
-
-
-
-
- |
`C
-
-
-
-
- foo
-
-
-
-
-
-
- |
`D
-
-
-
-
- bar
-
-
-
-
-
-
-
]
-
-
-
-
-
type empty_variant = |
-
-
-
-
-
type nonrec nonrec_ = int
-
-
-
-
-
type empty_conj =
-
-
-
-
- | X : [< `X of & 'a & int * float ] -> empty_conj
-
-
-
-
-
-
-
-
-
type conj =
-
-
-
-
- | X : [< `X of int & [< `B of int & float ] ] -> conj
-
-
-
-
-
-
-
-
-
val empty_conj : [< `X of & 'a & int * float ]
-
-
-
-
-
val conj : [< `X of int & [< `B of int & float ] ]
-
-
-
-
-
module Z : sig ... end
-
-
-
-
-
module X : sig ... end
-
-
-
-
-
module type PolyS = sig ... end
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Recent_impl/index.html b/test/html/expect/test_package+ml/Recent_impl/index.html
deleted file mode 100644
index bf8bc328fa..0000000000
--- a/test/html/expect/test_package+ml/Recent_impl/index.html
+++ /dev/null
@@ -1,53 +0,0 @@
-
-
-
-
- Recent_impl (test_package+ml.Recent_impl)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Recent_impl
-
-
-
- Module Recent_impl
-
-
-
-
-
-
module Foo : sig ... end
-
-
-
-
-
module B : sig ... end
-
-
-
-
-
-
module type S = sig ... end
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Section/index.html b/test/html/expect/test_package+ml/Section/index.html
deleted file mode 100644
index af8e7fa834..0000000000
--- a/test/html/expect/test_package+ml/Section/index.html
+++ /dev/null
@@ -1,99 +0,0 @@
-
-
-
-
- Section (test_package+ml.Section)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Section
-
-
-
-
-
-
-
- Empty section
-
-
- Text only
-
-
- Foo bar.
-
-
- Aside only
-
-
- Foo bar.
-
-
- Value only
-
-
-
- Empty section
-
-
-
- and one with a nested section
-
-
- This section
title has markup
-
-
- But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link.
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Stop/index.html b/test/html/expect/test_package+ml/Stop/index.html
deleted file mode 100644
index 6036981a49..0000000000
--- a/test/html/expect/test_package+ml/Stop/index.html
+++ /dev/null
@@ -1,60 +0,0 @@
-
-
-
-
- Stop (test_package+ml.Stop)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Stop
-
-
-
-
-
-
-
- This is normal commented text.
-
-
-
-
- The next value is bar
, and it should be missing from the documentation. There is also an entire module, M
, which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope.
-
-
- Documentation is on again.
-
-
- Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module.
-
-
-
-
module N : sig ... end
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Stop_dead_link_doc/index.html b/test/html/expect/test_package+ml/Stop_dead_link_doc/index.html
deleted file mode 100644
index 5e466b451f..0000000000
--- a/test/html/expect/test_package+ml/Stop_dead_link_doc/index.html
+++ /dev/null
@@ -1,119 +0,0 @@
-
-
-
-
- Stop_dead_link_doc (test_package+ml.Stop_dead_link_doc)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Stop_dead_link_doc
-
-
-
- Module Stop_dead_link_doc
-
-
-
-
-
-
module Foo : sig ... end
-
-
-
-
-
type foo =
-
-
-
-
- | Bar of Foo.t
-
-
-
-
-
-
-
-
-
type bar =
-
-
-
-
- | Bar of {
-
-
-
-
- field : Foo.t ;
-
-
-
-
- }
-
-
-
-
-
-
-
-
-
type foo_ =
-
-
-
-
- | Bar_ of int * Foo.t * int
-
-
-
-
-
-
-
-
-
type bar_ =
-
-
-
-
- | Bar__ of Foo.t option
-
-
-
-
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/Alias/index.html b/test/html/expect/test_package+ml/Toplevel_comments/Alias/index.html
deleted file mode 100644
index 260d7d513b..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/Alias/index.html
+++ /dev/null
@@ -1,39 +0,0 @@
-
-
-
-
- Alias (test_package+ml.Toplevel_comments.Alias)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » Alias
-
-
-
- Module Toplevel_comments.Alias
-
-
- Doc of Alias
.
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/Include_inline'/index.html b/test/html/expect/test_package+ml/Toplevel_comments/Include_inline'/index.html
deleted file mode 100644
index 8178bf1cb8..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/Include_inline'/index.html
+++ /dev/null
@@ -1,46 +0,0 @@
-
-
-
-
- Include_inline' (test_package+ml.Toplevel_comments.Include_inline')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » Include_inline'
-
-
-
- Module Toplevel_comments.Include_inline'
-
-
- Doc of Include_inline
, part 1.
-
-
- Doc of Include_inline
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/Include_inline/index.html b/test/html/expect/test_package+ml/Toplevel_comments/Include_inline/index.html
deleted file mode 100644
index 35bf9703c8..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/Include_inline/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- Include_inline (test_package+ml.Toplevel_comments.Include_inline)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » Include_inline
-
-
-
- Module Toplevel_comments.Include_inline
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/M''/index.html b/test/html/expect/test_package+ml/Toplevel_comments/M''/index.html
deleted file mode 100644
index c4ec998ba3..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/M''/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- M'' (test_package+ml.Toplevel_comments.M'')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » M''
-
-
-
- Module Toplevel_comments.M''
-
-
- Doc of M''
, part 1.
-
-
- Doc of M''
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/M'/index.html b/test/html/expect/test_package+ml/Toplevel_comments/M'/index.html
deleted file mode 100644
index 82badb81af..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/M'/index.html
+++ /dev/null
@@ -1,30 +0,0 @@
-
-
-
-
- M' (test_package+ml.Toplevel_comments.M')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » M'
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/M/index.html b/test/html/expect/test_package+ml/Toplevel_comments/M/index.html
deleted file mode 100644
index c5346d51da..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/M/index.html
+++ /dev/null
@@ -1,30 +0,0 @@
-
-
-
-
- M (test_package+ml.Toplevel_comments.M)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » M
-
-
-
- Module Toplevel_comments.M
-
-
- Doc of M
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/Ref_in_synopsis/index.html b/test/html/expect/test_package+ml/Toplevel_comments/Ref_in_synopsis/index.html
deleted file mode 100644
index 24a959fd92..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/Ref_in_synopsis/index.html
+++ /dev/null
@@ -1,39 +0,0 @@
-
-
-
-
- Ref_in_synopsis (test_package+ml.Toplevel_comments.Ref_in_synopsis)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » Ref_in_synopsis
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/class-c1/index.html b/test/html/expect/test_package+ml/Toplevel_comments/class-c1/index.html
deleted file mode 100644
index dd51569575..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/class-c1/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- c1 (test_package+ml.Toplevel_comments.c1)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » c1
-
-
-
- Class Toplevel_comments.c1
-
-
- Doc of c1
, part 1.
-
-
- Doc of c1
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/class-c2/index.html b/test/html/expect/test_package+ml/Toplevel_comments/class-c2/index.html
deleted file mode 100644
index a416f31ed7..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/class-c2/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- c2 (test_package+ml.Toplevel_comments.c2)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » c2
-
-
-
- Class Toplevel_comments.c2
-
-
- Doc of c2
.
-
-
- Doc of ct
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/class-type-ct/index.html b/test/html/expect/test_package+ml/Toplevel_comments/class-type-ct/index.html
deleted file mode 100644
index e4d4ea7f27..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/class-type-ct/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- ct (test_package+ml.Toplevel_comments.ct)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » ct
-
-
-
- Class type Toplevel_comments.ct
-
-
- Doc of ct
, part 1.
-
-
- Doc of ct
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/index.html b/test/html/expect/test_package+ml/Toplevel_comments/index.html
deleted file mode 100644
index 9d70529ddc..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/index.html
+++ /dev/null
@@ -1,161 +0,0 @@
-
-
-
-
- Toplevel_comments (test_package+ml.Toplevel_comments)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments
-
-
-
-
-
-
module type T = sig ... end
-
-
-
- Doc of T
, part 1.
-
-
-
-
-
-
-
- Doc of T
, part 2.
-
-
-
-
-
-
-
- Doc of Include_inline
, part 1.
-
-
-
-
-
-
-
- Doc of T
, part 2.
-
-
-
-
-
-
-
- Doc of Include_inline_T'
, part 1.
-
-
-
-
-
-
module M : sig ... end
-
-
-
-
-
-
module M' : sig ... end
-
-
-
- Doc of M'
from outside
-
-
-
-
-
-
module M'' : sig ... end
-
-
-
- Doc of M''
, part 1.
-
-
-
-
-
-
-
class c1 : int -> object ... end
-
-
-
- Doc of c1
, part 1.
-
-
-
-
-
-
class type ct = object ... end
-
-
-
- Doc of ct
, part 1.
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/module-type-Include_inline_T'/index.html b/test/html/expect/test_package+ml/Toplevel_comments/module-type-Include_inline_T'/index.html
deleted file mode 100644
index d0e264a753..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/module-type-Include_inline_T'/index.html
+++ /dev/null
@@ -1,46 +0,0 @@
-
-
-
-
- Include_inline_T' (test_package+ml.Toplevel_comments.Include_inline_T')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » Include_inline_T'
-
-
-
- Module type Toplevel_comments.Include_inline_T'
-
-
- Doc of Include_inline_T'
, part 1.
-
-
- Doc of Include_inline_T'
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/module-type-Include_inline_T/index.html b/test/html/expect/test_package+ml/Toplevel_comments/module-type-Include_inline_T/index.html
deleted file mode 100644
index 22611a0a32..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/module-type-Include_inline_T/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- Include_inline_T (test_package+ml.Toplevel_comments.Include_inline_T)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » Include_inline_T
-
-
-
- Module type Toplevel_comments.Include_inline_T
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Toplevel_comments/module-type-T/index.html b/test/html/expect/test_package+ml/Toplevel_comments/module-type-T/index.html
deleted file mode 100644
index c70e8597cf..0000000000
--- a/test/html/expect/test_package+ml/Toplevel_comments/module-type-T/index.html
+++ /dev/null
@@ -1,39 +0,0 @@
-
-
-
-
- T (test_package+ml.Toplevel_comments.T)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Toplevel_comments » T
-
-
-
- Module type Toplevel_comments.T
-
-
- Doc of T
, part 1.
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Type/index.html b/test/html/expect/test_package+ml/Type/index.html
deleted file mode 100644
index 5c22ee7710..0000000000
--- a/test/html/expect/test_package+ml/Type/index.html
+++ /dev/null
@@ -1,548 +0,0 @@
-
-
-
-
- Type (test_package+ml.Type)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Type
-
-
-
-
-
-
-
- Some documentation .
-
-
-
-
-
-
-
type private_ = private int
-
-
-
-
-
type 'a constructor = 'a
-
-
-
-
-
type arrow = int -> int
-
-
-
-
-
type higher_order = (int -> int) -> int
-
-
-
-
-
type labeled = l:int -> int
-
-
-
-
-
type optional = ?l:int -> int
-
-
-
-
-
type labeled_higher_order = (l:int -> int) -> (?l:int -> int) -> int
-
-
-
-
-
type pair = int * int
-
-
-
-
-
type parens_dropped = int * int
-
-
-
-
-
type triple = int * int * int
-
-
-
-
-
type nested_pair = (int * int) * int
-
-
-
-
-
-
-
type variant_e = {
-
-
}
-
-
-
-
-
type variant =
-
-
-
-
- | A
-
-
-
-
- | B of int
-
-
-
-
- | C
-
-
-
-
- foo
-
-
-
-
-
-
- | D
-
-
-
-
- bar
-
-
-
-
-
-
- | E of variant_e
-
-
-
-
-
-
-
-
-
type variant_c = {
-
-
}
-
-
-
-
-
-
type degenerate_gadt =
-
-
-
-
-
-
type private_variant = private
-
-
-
-
-
-
type record = {
-
-
-
-
- a : int;
-
-
-
-
- mutable b : int;
-
-
-
-
- c : int;
-
-
-
-
- foo
-
-
-
-
-
-
- d : int;
-
-
-
-
- bar
-
-
-
-
-
-
- e : a. 'a ;
-
-
-
-
-
}
-
-
-
-
-
type polymorphic_variant = [
-
-
-
-
- |
`A
-
-
-
-
- |
`B of int
-
-
-
-
- |
`C of int * unit
-
-
-
-
- |
`D
-
-
-
-
-
]
-
-
-
-
-
type polymorphic_variant_extension = [
-
-
]
-
-
-
-
-
type nested_polymorphic_variant = [
-
-
-
-
- |
`A of [ `B | `C ]
-
-
-
-
-
]
-
-
-
-
-
type private_extenion#row
-
-
-
-
-
and private_extenion = private [>
-
-
]
-
-
-
-
-
type object_ = < a : int; b : int; c : int; >
-
-
-
-
-
module type X = sig ... end
-
-
-
-
-
type module_ = (module X )
-
-
-
-
-
type module_substitution = (module X with type t = int and type u = unit)
-
-
-
-
-
-
type -'a contravariant
-
-
-
-
-
type _ bivariant = int
-
-
-
-
-
-
type using_binary = (int, int) binary
-
-
-
-
-
-
type 'a constrained = 'a constraint 'a = int
-
-
-
-
-
type 'a exact_variant = 'a constraint 'a = [ `A | `B of int ]
-
-
-
-
-
type 'a lower_variant = 'a constraint 'a = [> `A | `B of int ]
-
-
-
-
-
type 'a any_variant = 'a constraint 'a = [> ]
-
-
-
-
-
type 'a upper_variant = 'a constraint 'a = [< `A | `B of int ]
-
-
-
-
-
-
type 'a exact_object = 'a constraint 'a = < a : int; b : int; >
-
-
-
-
-
type 'a lower_object = 'a constraint 'a = < a : int; b : int; .. >
-
-
-
-
-
type 'a poly_object = 'a constraint 'a = < a : a. 'a ; >
-
-
-
-
-
type ('a, 'b) double_constrained = 'a * 'b constraint 'a = int constraint 'b = unit
-
-
-
-
-
type as_ = int as 'a * 'a
-
-
-
-
-
-
-
-
-
exception Foo of int * int
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/Type/module-type-X/index.html b/test/html/expect/test_package+ml/Type/module-type-X/index.html
deleted file mode 100644
index e69de29bb2..0000000000
diff --git a/test/html/expect/test_package+ml/Val/index.html b/test/html/expect/test_package+ml/Val/index.html
deleted file mode 100644
index d2e0dac64a..0000000000
--- a/test/html/expect/test_package+ml/Val/index.html
+++ /dev/null
@@ -1,53 +0,0 @@
-
-
-
-
- Val (test_package+ml.Val)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » Val
-
-
-
-
-
-
val documented : unit
-
-
-
-
-
-
val undocumented : unit
-
-
-
-
-
val documented_above : unit
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+ml/mld.html b/test/html/expect/test_package+ml/mld.html
deleted file mode 100644
index 114e38de66..0000000000
--- a/test/html/expect/test_package+ml/mld.html
+++ /dev/null
@@ -1,94 +0,0 @@
-
-
-
-
- mld (test_package+ml.mld)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+ml » mld
-
-
-
- Mld Page
-
-
- This is an .mld
file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do.
-
-
- It will have a TOC generated from section headings.
-
-
-
-
-
-
-
- Section
-
-
- This is a section.
-
-
- Another paragraph in section.
-
-
- Another section
-
-
- This is another section.
-
-
- Another paragraph in section 2.
-
-
- Subsection
-
-
- This is a subsection.
-
-
- Another paragraph in subsection.
-
-
- Yet another paragraph in subsection.
-
-
- Another Subsection
-
-
- This is another subsection.
-
-
- Another paragraph in subsection 2.
-
-
- Yet another paragraph in subsection 2.
-
-
-
-
diff --git a/test/html/expect/test_package+re/Alias/X/index.html b/test/html/expect/test_package+re/Alias/X/index.html
deleted file mode 100644
index 02d4b66783..0000000000
--- a/test/html/expect/test_package+re/Alias/X/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- X (test_package+re.Alias.X)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Alias » X
-
-
-
-
-
-
-
- Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X'
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Alias/index.html b/test/html/expect/test_package+re/Alias/index.html
deleted file mode 100644
index cf3c56c18e..0000000000
--- a/test/html/expect/test_package+re/Alias/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- Alias (test_package+re.Alias)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Alias
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Bugs/index.html b/test/html/expect/test_package+re/Bugs/index.html
deleted file mode 100644
index b6e7a85d17..0000000000
--- a/test/html/expect/test_package+re/Bugs/index.html
+++ /dev/null
@@ -1,43 +0,0 @@
-
-
-
-
- Bugs (test_package+re.Bugs)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Bugs
-
-
-
-
-
-
type opt('a) = option('a ) ;
-
-
-
-
-
let foo: ?bar:'a => unit => unit;
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Bugs_post_406/index.html b/test/html/expect/test_package+re/Bugs_post_406/index.html
deleted file mode 100644
index e2ecdf6703..0000000000
--- a/test/html/expect/test_package+re/Bugs_post_406/index.html
+++ /dev/null
@@ -1,41 +0,0 @@
-
-
-
-
- Bugs_post_406 (test_package+re.Bugs_post_406)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Bugs_post_406
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Bugs_pre_410/index.html b/test/html/expect/test_package+re/Bugs_pre_410/index.html
deleted file mode 100644
index 48e89703ec..0000000000
--- a/test/html/expect/test_package+re/Bugs_pre_410/index.html
+++ /dev/null
@@ -1,43 +0,0 @@
-
-
-
-
- Bugs_pre_410 (test_package+re.Bugs_pre_410)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Bugs_pre_410
-
-
-
- Module Bugs_pre_410
-
-
-
-
-
-
type opt'('a) = option(int) ;
-
-
-
-
-
let foo': ?bar:'a => unit => unit;
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Class/index.html b/test/html/expect/test_package+re/Class/index.html
deleted file mode 100644
index 63a47e387c..0000000000
--- a/test/html/expect/test_package+re/Class/index.html
+++ /dev/null
@@ -1,73 +0,0 @@
-
-
-
-
- Class (test_package+re.Class)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Class
-
-
-
-
-
-
class type empty = { ... }
-
-
-
-
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/External/index.html b/test/html/expect/test_package+re/External/index.html
deleted file mode 100644
index 4ef9a6b917..0000000000
--- a/test/html/expect/test_package+re/External/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- External (test_package+re.External)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » External
-
-
-
-
-
-
let foo: unit => unit;
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Functor/index.html b/test/html/expect/test_package+re/Functor/index.html
deleted file mode 100644
index 42ba894885..0000000000
--- a/test/html/expect/test_package+re/Functor/index.html
+++ /dev/null
@@ -1,63 +0,0 @@
-
-
-
-
- Functor (test_package+re.Functor)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Functor
-
-
-
-
-
-
module type S = { ... } ;
-
-
-
-
-
module type S1 = (_ : S ) => S ;
-
-
-
-
-
-
-
module F3 : (Arg : S ) => { ... } ;
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Include/index.html b/test/html/expect/test_package+re/Include/index.html
deleted file mode 100644
index c12e0a57ce..0000000000
--- a/test/html/expect/test_package+re/Include/index.html
+++ /dev/null
@@ -1,137 +0,0 @@
-
-
-
-
- Include (test_package+re.Include)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Include
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Include2/Y_include_doc/index.html b/test/html/expect/test_package+re/Include2/Y_include_doc/index.html
deleted file mode 100644
index a553bbbc64..0000000000
--- a/test/html/expect/test_package+re/Include2/Y_include_doc/index.html
+++ /dev/null
@@ -1,45 +0,0 @@
-
-
-
-
- Y_include_doc (test_package+re.Include2.Y_include_doc)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Include2 » Y_include_doc
-
-
-
- Module Include2.Y_include_doc
-
-
-
-
-
-
- Doc attached to include Y
. Y
's top-comment shouldn't appear here.
-
-
-
-
- include module type of struct include Y end ;
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Include2/Y_include_synopsis/index.html b/test/html/expect/test_package+re/Include2/Y_include_synopsis/index.html
deleted file mode 100644
index c3ed070b04..0000000000
--- a/test/html/expect/test_package+re/Include2/Y_include_synopsis/index.html
+++ /dev/null
@@ -1,43 +0,0 @@
-
-
-
-
- Y_include_synopsis (test_package+re.Include2.Y_include_synopsis)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Include2 » Y_include_synopsis
-
-
-
-
-
-
- include module type of struct include Y end ;
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Include2/index.html b/test/html/expect/test_package+re/Include2/index.html
deleted file mode 100644
index 1079c94b07..0000000000
--- a/test/html/expect/test_package+re/Include2/index.html
+++ /dev/null
@@ -1,78 +0,0 @@
-
-
-
-
- Include2 (test_package+re.Include2)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Include2
-
-
-
-
-
-
-
- Comment about X that should not appear when including X below.
-
-
-
-
-
-
- include module type of struct include X end ;
-
-
- Comment about X that should not appear when including X below.
-
-
-
-
-
-
-
-
- Top-comment of Y.
-
-
-
-
-
-
-
- The include Y
below should have the synopsis from Y
's top-comment attached to it.
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Include_sections/index.html b/test/html/expect/test_package+re/Include_sections/index.html
deleted file mode 100644
index 50c0ab8a35..0000000000
--- a/test/html/expect/test_package+re/Include_sections/index.html
+++ /dev/null
@@ -1,256 +0,0 @@
-
-
-
-
- Include_sections (test_package+re.Include_sections)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Include_sections
-
-
-
- Module Include_sections
-
-
-
-
-
-
-
-
- Let's include Something
once
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
- Second include
-
-
- Let's include Something
a second time: the heading level should be shift here.
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
- Third include
-
-
- Shifted some more.
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
- And let's include it again, but without inlining it this time: the ToC shouldn't grow.
-
-
-
-
- include Something ;
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Include_sections/module-type-Something/index.html b/test/html/expect/test_package+re/Include_sections/module-type-Something/index.html
deleted file mode 100644
index 2406c3857e..0000000000
--- a/test/html/expect/test_package+re/Include_sections/module-type-Something/index.html
+++ /dev/null
@@ -1,81 +0,0 @@
-
-
-
-
- Something (test_package+re.Include_sections.Something)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Include_sections » Something
-
-
-
- Module type Include_sections.Something
-
-
- A module type.
-
-
-
-
-
-
-
-
- Something 1
-
-
- foo
-
-
-
- Something 2
-
-
-
- Something 1-bis
-
-
- Some text.
-
-
-
-
diff --git a/test/html/expect/test_package+re/Interlude/index.html b/test/html/expect/test_package+re/Interlude/index.html
deleted file mode 100644
index 2bbfa97f37..0000000000
--- a/test/html/expect/test_package+re/Interlude/index.html
+++ /dev/null
@@ -1,81 +0,0 @@
-
-
-
-
- Interlude (test_package+re.Interlude)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Interlude
-
-
-
-
- Some separate stray text at the top of the module.
-
-
-
- Some stray text that is not associated with any signature item.
-
-
- It has multiple paragraphs.
-
-
- A separate block of stray text, adjacent to the preceding one.
-
-
-
-
-
-
- Stray text at the bottom of the module.
-
-
-
-
diff --git a/test/html/expect/test_package+re/Labels/index.html b/test/html/expect/test_package+re/Labels/index.html
deleted file mode 100644
index e46af4c2d4..0000000000
--- a/test/html/expect/test_package+re/Labels/index.html
+++ /dev/null
@@ -1,237 +0,0 @@
-
-
-
-
- Labels (test_package+re.Labels)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Labels
-
-
-
-
-
-
-
- Attached to unit
-
-
- Attached to nothing
-
-
-
-
-
-
-
- Attached to value
-
-
-
-
-
-
-
- Attached to external
-
-
-
-
-
-
module type S = { ... } ;
-
-
-
-
-
-
class type cs = { ... }
-
-
-
-
-
-
- Attached to exception
-
-
-
-
-
-
-
-
- Attached to extension
-
-
-
-
-
-
-
- Attached to module subst
-
-
-
-
-
-
-
- Attached to type subst
-
-
-
-
-
-
type u =
-
-
-
-
- | A'
-
-
-
-
- Attached to constructor
-
-
-
-
-
-
-
;
-
-
-
-
-
type v = {
-
-
-
-
- f: t ,
-
-
-
-
- Attached to field
-
-
-
-
-
-
-
} ;
-
-
-
- Testing that labels can be referenced
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Markup/index.html b/test/html/expect/test_package+re/Markup/index.html
deleted file mode 100644
index 075a552e7c..0000000000
--- a/test/html/expect/test_package+re/Markup/index.html
+++ /dev/null
@@ -1,378 +0,0 @@
-
-
-
-
- Markup (test_package+re.Markup)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Markup
-
-
-
-
-
-
-
- Sections
-
-
- Let's get these done first, because sections will be used to break up the rest of this test.
-
-
- Besides the section heading above, there are also
-
-
- Subsection headings
-
-
- and
-
-
- Sub-subsection headings
-
-
- but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files.
-
-
- Anchors
-
-
- Sections can have attached Anchors , and it is possible to link to them. Links to section headers should not be set in source code style.
-
-
- Paragraph
-
-
- Individual paragraphs can have a heading.
-
-
- Subparagraph
-
-
- Parts of a longer paragraph that can be considered alone can also have headings.
-
-
- Styling
-
-
- This paragraph has some styled elements: bold and italic , bold italic , emphasis , emphasis within emphasis , bold italic , superscript , subscript . The line spacing should be enough for superscripts and subscripts not to look odd.
-
-
- Note: In italics emphasis is rendered as normal text while emphasis in emphasis is rendered in italics. It also work the same in links in italics with emphasis in emphasis .
-
-
- code
is a different kind of markup that doesn't allow nested markup.
-
-
- It's possible for two markup elements to appear next to each other and have a space, and appear next to each other with no space. It doesn't matter how much space it was in the source: in this sentence, it was two space characters. And in this one, there is a newline .
-
-
- This is also true between non- code
markup and code
.
-
-
- Code can appear inside other
markup . Its display shouldn't be affected.
-
-
- Links and references
-
-
- This is a link . It sends you to the top of this page. Links can have markup inside them: bold , italics , emphasis , superscript , subscript , and code
. Links can also be nested inside markup. Links cannot be nested inside each other. This link has no replacement text: # . The text is filled in by odoc. This is a shorthand link: # . The text is also filled in by odoc in this case.
-
-
- This is a reference to foo
. References can have replacement text: the value foo . Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: bold , italic , emphasis , superscript , subscript , and code
. It's also possible to surround a reference in a style: foo
. References can't be nested inside references, and links and references can't be nested inside each other.
-
-
- Preformatted text
-
-
- This is a code block:
-
-
let foo = ()
-(** There are some nested comments in here, but an unpaired comment
- terminator would terminate the whole doc surrounding comment. It's
- best to keep code blocks no wider than 72 characters. *)
-
-let bar =
- ignore foo
-
- There are also verbatim blocks:
-
-
The main difference is these don't get syntax highlighting.
-
- Lists
-
-
-
- This is a
-
-
- shorthand bulleted list,
-
-
- and the paragraphs in each list item support styling .
-
-
-
-
- This is a
-
-
- shorthand numbered list.
-
-
-
-
- Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break
-
-
-
- just creates a paragraph outside the list.
-
-
-
- Similarly, inserting a blank line between two list items
-
-
-
-
- creates two separate lists.
-
-
-
-
-
- but there is also the numbered variant.
-
-
-
-
-
-
- lists
-
-
- can be nested
-
-
- and can include references
-
-
- foo
-
-
-
-
-
- Unicode
-
-
- The parser supports any ASCII-compatible encoding, in particuλar UTF-8.
-
-
- Raw HTML
-
-
- Raw HTML can be as inline elements into sentences.
-
-
- If the raw HTML is the only thing in a paragraph, it is treated as a block
- element, and won't be wrapped in paragraph tags by the HTML generator.
-
-
- Modules
-
-
-
-
-
- X
-
-
- Y
-
-
- Z
-
-
-
-
- Each comment can end with zero or more tags. Here are some examples:
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- Comments in structure items support markup , to o .
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Module/index.html b/test/html/expect/test_package+re/Module/index.html
deleted file mode 100644
index 2a7dade220..0000000000
--- a/test/html/expect/test_package+re/Module/index.html
+++ /dev/null
@@ -1,111 +0,0 @@
-
-
-
-
- Module (test_package+re.Module)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Module
-
-
-
- Module Module
-
-
- Foo.
-
-
-
-
-
-
-
module type S = { ... } ;
-
-
-
-
-
-
-
module type S3 = S with type t = int and type u = string ;
-
-
-
-
-
module type S4 = S with type t := int ;
-
-
-
-
-
module type S5 = S with type v ('a) := list('a ) ;
-
-
-
-
-
-
module type S6 = S with type w ('a, 'b) := result ('a , 'b ) ;
-
-
-
-
-
-
module type S7 = S with module M = M' ;
-
-
-
-
-
module type S8 = S with module M := M' ;
-
-
-
-
-
module type S9 = module type of M' ;
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/F/argument-1-Arg1/index.html b/test/html/expect/test_package+re/Nested/F/argument-1-Arg1/index.html
deleted file mode 100644
index 5c31813a5e..0000000000
--- a/test/html/expect/test_package+re/Nested/F/argument-1-Arg1/index.html
+++ /dev/null
@@ -1,64 +0,0 @@
-
-
-
-
- Arg1 (test_package+re.Nested.F.1-Arg1)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » F » 1-Arg1
-
-
-
- Parameter F.1-Arg1
-
-
-
-
-
-
-
- Type
-
-
-
- Values
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/F/argument-2-Arg2/index.html b/test/html/expect/test_package+re/Nested/F/argument-2-Arg2/index.html
deleted file mode 100644
index cd654a1c6a..0000000000
--- a/test/html/expect/test_package+re/Nested/F/argument-2-Arg2/index.html
+++ /dev/null
@@ -1,48 +0,0 @@
-
-
-
-
- Arg2 (test_package+re.Nested.F.2-Arg2)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » F » 2-Arg2
-
-
-
- Parameter F.2-Arg2
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/F/index.html b/test/html/expect/test_package+re/Nested/F/index.html
deleted file mode 100644
index b49b213b22..0000000000
--- a/test/html/expect/test_package+re/Nested/F/index.html
+++ /dev/null
@@ -1,76 +0,0 @@
-
-
-
-
- F (test_package+re.Nested.F)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » F
-
-
-
-
-
-
-
- Type
-
-
- Parameters
-
-
-
-
- Signature
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/X/index.html b/test/html/expect/test_package+re/Nested/X/index.html
deleted file mode 100644
index de625410de..0000000000
--- a/test/html/expect/test_package+re/Nested/X/index.html
+++ /dev/null
@@ -1,70 +0,0 @@
-
-
-
-
- X (test_package+re.Nested.X)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » X
-
-
-
-
-
-
-
- Type
-
-
-
- Values
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/class-inherits/index.html b/test/html/expect/test_package+re/Nested/class-inherits/index.html
deleted file mode 100644
index 74d84d11c3..0000000000
--- a/test/html/expect/test_package+re/Nested/class-inherits/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- inherits (test_package+re.Nested.inherits)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » inherits
-
-
-
- Class Nested.inherits
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/class-z/index.html b/test/html/expect/test_package+re/Nested/class-z/index.html
deleted file mode 100644
index bb1f695cb1..0000000000
--- a/test/html/expect/test_package+re/Nested/class-z/index.html
+++ /dev/null
@@ -1,74 +0,0 @@
-
-
-
-
- z (test_package+re.Nested.z)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » z
-
-
-
-
-
-
-
-
-
-
val mutable virtual y': int
-
-
-
- Methods
-
-
-
-
-
method private virtual z': int
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/index.html b/test/html/expect/test_package+re/Nested/index.html
deleted file mode 100644
index 73bfd919c8..0000000000
--- a/test/html/expect/test_package+re/Nested/index.html
+++ /dev/null
@@ -1,104 +0,0 @@
-
-
-
-
- Nested (test_package+re.Nested)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested
-
-
-
-
-
-
-
- Module
-
-
-
-
-
- This is module X.
-
-
-
-
- Module type
-
-
-
-
module type Y = { ... } ;
-
-
-
- This is module type Y.
-
-
-
-
- Functor
-
-
-
-
module F : (Arg1 : Y ) => (Arg2 : { ... }) => { ... } ;
-
-
-
- This is a functor F.
-
-
-
-
- Class
-
-
-
-
class virtual z : { ... }
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Nested/module-type-Y/index.html b/test/html/expect/test_package+re/Nested/module-type-Y/index.html
deleted file mode 100644
index 21bee76fa0..0000000000
--- a/test/html/expect/test_package+re/Nested/module-type-Y/index.html
+++ /dev/null
@@ -1,70 +0,0 @@
-
-
-
-
- Y (test_package+re.Nested.Y)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Nested » Y
-
-
-
-
-
-
-
- Type
-
-
-
- Values
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Ocamlary/index.html b/test/html/expect/test_package+re/Ocamlary/index.html
deleted file mode 100644
index 6c19ea4d56..0000000000
--- a/test/html/expect/test_package+re/Ocamlary/index.html
+++ /dev/null
@@ -1,2037 +0,0 @@
-
-
-
-
- Ocamlary (test_package+re.Ocamlary)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Ocamlary
-
-
-
- Module Ocamlary
-
-
- This is an interface with all of the module system features. This documentation demonstrates:
-
-
-
- A numbered list:
-
-
-
- 3
-
-
- 2
-
-
- 1
-
-
-
- David Sheets is the author.
-
-
-
-
-
-
-
-
- You may find more information about this HTML documentation renderer at github.com/dsheets/ocamlary .
-
-
- This is some verbatim text:
-
-
verbatim
-
- This is some verbatim text:
-
-
[][df[]]}}
-
- Here is some raw LaTeX:
-
-
- Here is an index table of Empty
modules:
-
-
-
- Empty
A plain, empty module
-
-
- EmptyAlias
A plain module alias of Empty
-
-
-
- Here is a table of links to indexes: indexlist
-
-
- Here is some superscript: x2
-
-
- Here is some subscript: x0
-
-
- Here are some escaped brackets: { [ @ ] }
-
-
- Here is some emphasis followed by code
.
-
-
- An unassociated comment
-
-
- Level 1
-
-
- Level 2
-
-
- Level 3
-
-
- Level 4
-
-
- Basic module stuff
-
-
-
-
module Empty : { ... } ;
-
-
-
- A plain, empty module
-
-
-
-
-
-
module type Empty = { ... } ;
-
-
-
- An ambiguous, misnamed module type
-
-
-
-
-
-
-
- An ambiguous, misnamed module type
-
-
-
-
- Section 9000
-
-
-
-
module EmptyAlias = Empty ;
-
-
-
- A plain module alias of Empty
-
-
-
-
- EmptySig
-
-
-
-
-
- A plain, empty module signature
-
-
-
-
-
-
-
- A plain, empty module signature alias of
-
-
-
-
-
-
-
- A plain module of a signature of EmptySig
(reference)
-
-
-
-
-
-
-
- A plain module with an alias signature
-
-
-
-
-
-
-
-
- There's a signature in a module in this signature.
-
-
-
-
-
- For a good time, see SuperSig
.SubSigA.subSig or SuperSig
.SubSigB.subSig or SuperSig.EmptySig
. Section Section 9000 is also interesting. EmptySig is the section and EmptySig
is the module signature.
-
-
-
- Some text before exception title.
-
-
- Basic exception stuff
-
-
- After exception title.
-
-
-
-
exception Kaboom (unit);
-
-
-
- Unary exception constructor
-
-
-
-
-
-
exception Kablam (unit, unit);
-
-
-
- Binary exception constructor
-
-
-
-
-
-
exception Kapow ((unit, unit) );
-
-
-
- Unary exception constructor over binary tuple
-
-
-
-
-
-
-
exception EmptySigAlias ;
-
-
-
-
-
-
-
type a_function('a, 'b) = 'a => 'b ;
-
-
-
-
-
-
let a_function: x:int => int;
-
-
-
- This is a_function
with param and return type.
-
-
-
-
-
-
-
-
-
let fun_maybe: ?yes:unit => unit => int;
-
-
-
-
-
let not_found: unit => unit;
-
-
-
-
-
-
let ocaml_org: string;
-
-
-
-
-
-
let some_file: string;
-
-
-
-
-
-
let some_doc: string;
-
-
-
-
-
-
let since_mesozoic: unit;
-
-
-
- This value was introduced in the Mesozoic era.
-
-
-
-
-
-
-
-
- This value has had changes in 1.0.0, 1.1.0, and 1.2.0.
-
-
-
-
-
-
-
- Some Operators
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- Advanced Module Stuff
-
-
-
-
-
- This comment is for CollectionModule
.
-
-
-
-
-
-
-
-
module type MMM = { ... } ;
-
-
-
-
-
-
-
module type A = { ... } ;
-
-
-
-
-
module type B = { ... } ;
-
-
-
-
-
module type C = { ... } ;
-
-
-
- This module type includes two signatures.
-
-
-
-
-
-
-
- This comment is for FunctorTypeOf
.
-
-
-
-
-
-
-
- This comment is for IncludeModuleType
.
-
-
-
-
-
-
- Advanced Type Stuff
-
-
-
-
type record = {
-
-
-
-
- field1: int,
-
-
-
-
- This comment is for field1
.
-
-
-
-
-
-
- field2: int,
-
-
-
-
- This comment is for field2
.
-
-
-
-
-
-
-
} ;
-
-
-
- This comment is for record
.
-
-
- This comment is also for record
.
-
-
-
-
-
-
type mutable_record = {
-
-
-
-
- mutable a: int,
-
-
-
-
- a
is first and mutable
-
-
-
-
-
-
- b: unit,
-
-
-
-
- b
is second and immutable
-
-
-
-
-
-
- mutable c: int,
-
-
-
-
- c
is third and mutable
-
-
-
-
-
-
-
} ;
-
-
-
-
-
type universe_record = {
-
-
-
-
- nihilate: a. 'a => unit,
-
-
-
-
-
} ;
-
-
-
-
-
type variant =
-
-
-
-
- | TagA
-
-
-
-
- This comment is for TagA
.
-
-
-
-
-
-
- | ConstrB (int)
-
-
-
-
- This comment is for ConstrB
.
-
-
-
-
-
-
- | ConstrC (int, int)
-
-
-
-
- This comment is for binary ConstrC
.
-
-
-
-
-
-
- | ConstrD ((int, int) )
-
-
-
-
- This comment is for unary ConstrD
of binary tuple.
-
-
-
-
-
-
-
;
-
-
-
- This comment is for variant
.
-
-
- This comment is also for variant
.
-
-
-
-
-
-
type poly_variant = [
-
-
-
-
- |
`TagA
-
-
-
-
- |
`ConstrB(int)
-
-
-
-
-
] ;
-
-
-
- This comment is for poly_variant
.
-
-
- Wow! It was a polymorphic variant!
-
-
-
-
-
-
type full_gadt(_, _) =
-
-
-
-
- | Tag : full_gadt (unit, unit)
-
-
-
-
- | First ('a ) : full_gadt ('a , unit)
-
-
-
-
- | Second ('a ) : full_gadt (unit, 'a )
-
-
-
-
- | Exist ('a , 'b ) : full_gadt ('b , unit)
-
-
-
-
-
;
-
-
-
- This comment is for full_gadt
.
-
-
- Wow! It was a GADT!
-
-
-
-
-
-
type partial_gadt('a) =
-
-
;
-
-
-
- This comment is for partial_gadt
.
-
-
- Wow! It was a mixed GADT!
-
-
-
-
-
-
-
- This comment is for alias
.
-
-
-
-
-
-
-
- This comment is for tuple
.
-
-
-
-
-
-
type variant_alias = variant =
-
-
-
-
- | TagA
-
-
-
-
- | ConstrB (int)
-
-
-
-
- | ConstrC (int, int)
-
-
-
-
- | ConstrD ((int, int) )
-
-
-
-
-
;
-
-
-
- This comment is for variant_alias
.
-
-
-
-
-
-
type record_alias = record = {
-
-
-
-
- field1: int,
-
-
-
-
- field2: int,
-
-
-
-
-
} ;
-
-
-
- This comment is for record_alias
.
-
-
-
-
-
-
type poly_variant_union = [
-
-
] ;
-
-
-
- This comment is for poly_variant_union
.
-
-
-
-
-
-
type poly_poly_variant('a) = [
-
-
-
-
- |
`TagA('a )
-
-
-
-
-
] ;
-
-
-
-
-
type bin_poly_poly_variant('a, 'b) = [
-
-
-
-
- |
`TagA('a )
-
-
-
-
- |
`ConstrB('b )
-
-
-
-
-
] ;
-
-
-
-
-
type open_poly_variant('a) = [> `TagA ] as 'a ;
-
-
-
-
-
type open_poly_variant2('a) = [> `ConstrB(int) ] as 'a ;
-
-
-
-
-
-
type poly_fun('a) = [> `ConstrB(int) ] as 'a => 'a ;
-
-
-
-
-
type poly_fun_constraint('a) = 'a => 'a constraint 'a = [> `TagA ] ;
-
-
-
-
-
type closed_poly_variant('a) = [< `One | `Two ] as 'a ;
-
-
-
-
-
type clopen_poly_variant('a) = [< `One | `Two (int) | `Three Two Three ] as 'a ;
-
-
-
-
-
type nested_poly_variant = [
-
-
-
-
- |
`A
-
-
-
-
- |
`B([ `B1 | `B2 ] )
-
-
-
-
- |
`C
-
-
-
-
- |
`D([ `D1([ `D1a ] ) ] )
-
-
-
-
-
] ;
-
-
-
-
-
type full_gadt_alias('a, 'b) = full_gadt ('a , 'b ) =
-
-
;
-
-
-
- This comment is for full_gadt_alias
.
-
-
-
-
-
-
-
- This comment is for partial_gadt_alias
.
-
-
-
-
-
-
exception Exn_arrow (unit) : exn;
-
-
-
-
-
-
type mutual_constr_a =
-
-
;
-
-
-
-
-
-
and mutual_constr_b =
-
-
-
-
- | B
-
-
-
-
- | A_ish (mutual_constr_a )
-
-
-
-
- This comment must be here for the next to associate correctly.
-
-
-
-
-
-
-
;
-
-
-
-
-
-
type rec_obj = {. f: int, g: unit => unit, h: rec_obj , } ;
-
-
-
-
-
type open_obj('a) = {.. f: int, g: unit => unit, } as 'a ;
-
-
-
-
-
type oof('a) = {.. a: unit, } as 'a => 'a ;
-
-
-
-
-
type any_obj('a) = {.. } as 'a ;
-
-
-
-
-
type empty_obj = {. } ;
-
-
-
-
-
type one_meth = {. meth: unit, } ;
-
-
-
-
-
-
- A mystery wrapped in an ellipsis
-
-
-
-
-
-
-
-
type ext +=
-
-
-
-
- | ExtC (unit)
-
-
-
-
- | ExtD (ext )
-
-
-
-
-
;
-
-
-
-
-
-
-
type poly_ext('a) = .. ;
-
-
-
-
-
-
type poly_ext +=
-
-
-
-
- | Foo ('b )
-
-
-
-
- | Bar ('b , 'b )
-
-
-
-
- 'b poly_ext
-
-
-
-
-
-
-
;
-
-
-
-
-
type poly_ext +=
-
-
-
-
- | Quux ('c )
-
-
-
-
- 'c poly_ext
-
-
-
-
-
-
-
;
-
-
-
-
-
-
type ExtMod.t +=
-
-
-
-
- | ZzzTop0
-
-
-
-
- It's got the rock
-
-
-
-
-
-
-
;
-
-
-
-
-
type ExtMod.t +=
-
-
-
-
- | ZzzTop (unit)
-
-
-
-
- and it packs a unit.
-
-
-
-
-
-
-
;
-
-
-
-
-
let launch_missiles: unit => unit;
-
-
-
- Rotate keys on my mark...
-
-
-
-
-
-
-
- A brown paper package tied up with string
-
-
-
-
-
-
-
-
-
-
-
type my_unit_class('a) = param_class (unit) as 'a ;
-
-
-
-
-
module Dep1 : { ... } ;
-
-
-
-
-
module Dep2 : (Arg : { ... }) => { ... } ;
-
-
-
-
-
-
module Dep3 : { ... } ;
-
-
-
-
-
module Dep4 : { ... } ;
-
-
-
-
-
module Dep5 : (Arg : { ... }) => { ... } ;
-
-
-
-
-
-
-
module Dep6 : { ... } ;
-
-
-
-
-
module Dep7 : (Arg : { ... }) => { ... } ;
-
-
-
-
-
-
module Dep8 : { ... } ;
-
-
-
-
-
module Dep9 : (X : { ... }) => { ... } ;
-
-
-
-
-
-
module Dep11 : { ... } ;
-
-
-
-
-
module Dep12 : (Arg : { ... }) => { ... } ;
-
-
-
-
-
-
-
module type With1 = { ... } ;
-
-
-
-
-
module With2 : { ... } ;
-
-
-
-
-
-
-
-
-
module With5 : { ... } ;
-
-
-
-
-
module With6 : { ... } ;
-
-
-
-
-
module With7 : (X : { ... }) => { ... } ;
-
-
-
-
-
-
module With9 : { ... } ;
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- Trying the {!modules: ...} command.
-
-
- With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references.
-
-
- With odoc, everything should be resolved (and linked) but only toplevel units will be documented.
-
-
-
- Weirder usages involving module types
-
-
-
- IncludeInclude1
.IncludeInclude2
-
-
- Dep4
.T
-
-
- A.Q
-
-
-
- Playing with @canonical paths
-
-
-
-
- Aliases again
-
-
-
-
-
- Let's imitate jst's layout.
-
-
-
-
- Section title splicing
-
-
- I can refer to
-
-
-
- But also to things in submodules:
-
-
-
- {!section:SuperSig.SubSigA.subSig}
: SuperSig
.SubSigA.subSig
-
-
- {!Aliases.incl}
: Aliases:incl
-
-
-
- And just to make sure we do not mess up:
-
-
-
- {{!section:indexmodules}A}
: A
-
-
- {{!aliases}B}
: B
-
-
- {{!section:SuperSig.SubSigA.subSig}C}
: C
-
-
- {{!Aliases.incl}D}
: D
-
-
-
- New reference syntax
-
-
-
-
module type M = { ... } ;
-
-
-
-
- Here goes:
-
-
-
- {!module-M.t}
: M.t
-
-
- {!module-type-M.t}
: M.t
-
-
-
-
- Some here should fail:
-
-
-
- {!Only_a_module.t}
: Only_a_module.t
-
-
- {!module-Only_a_module.t}
: Only_a_module.t
-
-
- {!module-type-Only_a_module.t}
: Only_a_module
.t : test
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Recent/X/index.html b/test/html/expect/test_package+re/Recent/X/index.html
deleted file mode 100644
index c6fb745abc..0000000000
--- a/test/html/expect/test_package+re/Recent/X/index.html
+++ /dev/null
@@ -1,48 +0,0 @@
-
-
-
-
- X (test_package+re.Recent.X)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Recent » X
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Recent/index.html b/test/html/expect/test_package+re/Recent/index.html
deleted file mode 100644
index cfb590ce4d..0000000000
--- a/test/html/expect/test_package+re/Recent/index.html
+++ /dev/null
@@ -1,248 +0,0 @@
-
-
-
-
- Recent (test_package+re.Recent)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Recent
-
-
-
-
-
-
module type S = { ... } ;
-
-
-
-
-
module type S1 = (_ : S ) => S ;
-
-
-
-
-
type variant =
-
-
-
-
- | A
-
-
-
-
- | B (int)
-
-
-
-
- | C
-
-
-
-
- foo
-
-
-
-
-
-
- | D
-
-
-
-
- bar
-
-
-
-
-
-
- | E of {
-
- }
-
-
-
-
-
;
-
-
-
-
-
type gadt(_) =
-
-
-
-
- | A : gadt (int)
-
-
-
-
- | B (int) : gadt (string)
-
-
-
-
- foo
-
-
-
-
-
-
- | C : {
-
- } : gadt (unit)
-
-
-
-
-
;
-
-
-
-
-
type polymorphic_variant = [
-
-
-
-
- |
`A
-
-
-
-
- |
`B(int)
-
-
-
-
- |
`C
-
-
-
-
- foo
-
-
-
-
-
-
- |
`D
-
-
-
-
- bar
-
-
-
-
-
-
-
] ;
-
-
-
-
-
type empty_variant = | ;
-
-
-
-
-
type nonrec nonrec_ = int ;
-
-
-
-
-
type empty_conj =
-
-
-
-
- | X ([< `X& ('a ) & ((int, float) ) ] ) : empty_conj
-
-
-
-
-
;
-
-
-
-
-
type conj =
-
-
-
-
- | X ([< `X(int) & ([< `B(int) & (float) ] ) ] ) : conj
-
-
-
-
-
;
-
-
-
-
-
let empty_conj: [< `X& ('a ) & ((int, float) ) ] ;
-
-
-
-
-
let conj: [< `X(int) & ([< `B(int) & (float) ] ) ] ;
-
-
-
-
-
-
-
module type PolyS = { ... } ;
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Recent_impl/index.html b/test/html/expect/test_package+re/Recent_impl/index.html
deleted file mode 100644
index 801363b044..0000000000
--- a/test/html/expect/test_package+re/Recent_impl/index.html
+++ /dev/null
@@ -1,53 +0,0 @@
-
-
-
-
- Recent_impl (test_package+re.Recent_impl)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Recent_impl
-
-
-
- Module Recent_impl
-
-
-
-
-
-
-
-
-
module type S = { ... } ;
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Section/index.html b/test/html/expect/test_package+re/Section/index.html
deleted file mode 100644
index df1cb6e2d0..0000000000
--- a/test/html/expect/test_package+re/Section/index.html
+++ /dev/null
@@ -1,99 +0,0 @@
-
-
-
-
- Section (test_package+re.Section)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Section
-
-
-
-
-
-
-
- Empty section
-
-
- Text only
-
-
- Foo bar.
-
-
- Aside only
-
-
- Foo bar.
-
-
- Value only
-
-
-
- Empty section
-
-
-
- and one with a nested section
-
-
- This section
title has markup
-
-
- But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link.
-
-
-
-
diff --git a/test/html/expect/test_package+re/Stop/index.html b/test/html/expect/test_package+re/Stop/index.html
deleted file mode 100644
index bbee100c37..0000000000
--- a/test/html/expect/test_package+re/Stop/index.html
+++ /dev/null
@@ -1,60 +0,0 @@
-
-
-
-
- Stop (test_package+re.Stop)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Stop
-
-
-
-
-
-
-
- This is normal commented text.
-
-
-
-
- The next value is bar
, and it should be missing from the documentation. There is also an entire module, M
, which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope.
-
-
- Documentation is on again.
-
-
- Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module.
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Stop_dead_link_doc/index.html b/test/html/expect/test_package+re/Stop_dead_link_doc/index.html
deleted file mode 100644
index c8a34efc8c..0000000000
--- a/test/html/expect/test_package+re/Stop_dead_link_doc/index.html
+++ /dev/null
@@ -1,123 +0,0 @@
-
-
-
-
- Stop_dead_link_doc (test_package+re.Stop_dead_link_doc)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Stop_dead_link_doc
-
-
-
- Module Stop_dead_link_doc
-
-
-
-
-
-
-
type foo =
-
-
-
-
- | Bar (Foo.t )
-
-
-
-
-
;
-
-
-
-
-
type bar =
-
-
-
-
- | Bar of {
-
-
-
-
- field: Foo.t ,
-
-
-
-
- }
-
-
-
-
-
;
-
-
-
-
-
type foo_ =
-
-
-
-
- | Bar_ ((int, Foo.t ) , int)
-
-
-
-
-
;
-
-
-
-
-
type bar_ =
-
-
-
-
- | Bar__ (option(Foo.t ))
-
-
-
-
-
;
-
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/Alias/index.html b/test/html/expect/test_package+re/Toplevel_comments/Alias/index.html
deleted file mode 100644
index cb75db16c6..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/Alias/index.html
+++ /dev/null
@@ -1,39 +0,0 @@
-
-
-
-
- Alias (test_package+re.Toplevel_comments.Alias)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » Alias
-
-
-
- Module Toplevel_comments.Alias
-
-
- Doc of Alias
.
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/Include_inline'/index.html b/test/html/expect/test_package+re/Toplevel_comments/Include_inline'/index.html
deleted file mode 100644
index fa7f8be9de..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/Include_inline'/index.html
+++ /dev/null
@@ -1,46 +0,0 @@
-
-
-
-
- Include_inline' (test_package+re.Toplevel_comments.Include_inline')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » Include_inline'
-
-
-
- Module Toplevel_comments.Include_inline'
-
-
- Doc of Include_inline
, part 1.
-
-
- Doc of Include_inline
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/Include_inline/index.html b/test/html/expect/test_package+re/Toplevel_comments/Include_inline/index.html
deleted file mode 100644
index 695ea70d77..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/Include_inline/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- Include_inline (test_package+re.Toplevel_comments.Include_inline)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » Include_inline
-
-
-
- Module Toplevel_comments.Include_inline
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/M''/index.html b/test/html/expect/test_package+re/Toplevel_comments/M''/index.html
deleted file mode 100644
index afecb069bf..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/M''/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- M'' (test_package+re.Toplevel_comments.M'')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » M''
-
-
-
- Module Toplevel_comments.M''
-
-
- Doc of M''
, part 1.
-
-
- Doc of M''
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/M'/index.html b/test/html/expect/test_package+re/Toplevel_comments/M'/index.html
deleted file mode 100644
index 1d13e2c76c..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/M'/index.html
+++ /dev/null
@@ -1,30 +0,0 @@
-
-
-
-
- M' (test_package+re.Toplevel_comments.M')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » M'
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/M/index.html b/test/html/expect/test_package+re/Toplevel_comments/M/index.html
deleted file mode 100644
index a016b4a977..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/M/index.html
+++ /dev/null
@@ -1,30 +0,0 @@
-
-
-
-
- M (test_package+re.Toplevel_comments.M)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » M
-
-
-
- Module Toplevel_comments.M
-
-
- Doc of M
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/Ref_in_synopsis/index.html b/test/html/expect/test_package+re/Toplevel_comments/Ref_in_synopsis/index.html
deleted file mode 100644
index 0829ecb92d..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/Ref_in_synopsis/index.html
+++ /dev/null
@@ -1,39 +0,0 @@
-
-
-
-
- Ref_in_synopsis (test_package+re.Toplevel_comments.Ref_in_synopsis)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » Ref_in_synopsis
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/class-c1/index.html b/test/html/expect/test_package+re/Toplevel_comments/class-c1/index.html
deleted file mode 100644
index 80219902be..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/class-c1/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- c1 (test_package+re.Toplevel_comments.c1)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » c1
-
-
-
- Class Toplevel_comments.c1
-
-
- Doc of c1
, part 1.
-
-
- Doc of c1
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/class-c2/index.html b/test/html/expect/test_package+re/Toplevel_comments/class-c2/index.html
deleted file mode 100644
index b0d3517d1b..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/class-c2/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- c2 (test_package+re.Toplevel_comments.c2)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » c2
-
-
-
- Class Toplevel_comments.c2
-
-
- Doc of c2
.
-
-
- Doc of ct
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/class-type-ct/index.html b/test/html/expect/test_package+re/Toplevel_comments/class-type-ct/index.html
deleted file mode 100644
index 02cc3df7fe..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/class-type-ct/index.html
+++ /dev/null
@@ -1,33 +0,0 @@
-
-
-
-
- ct (test_package+re.Toplevel_comments.ct)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » ct
-
-
-
- Class type Toplevel_comments.ct
-
-
- Doc of ct
, part 1.
-
-
- Doc of ct
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/index.html b/test/html/expect/test_package+re/Toplevel_comments/index.html
deleted file mode 100644
index e18e2e6639..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/index.html
+++ /dev/null
@@ -1,161 +0,0 @@
-
-
-
-
- Toplevel_comments (test_package+re.Toplevel_comments)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments
-
-
-
-
-
-
module type T = { ... } ;
-
-
-
- Doc of T
, part 1.
-
-
-
-
-
-
-
- Doc of T
, part 2.
-
-
-
-
-
-
-
- Doc of Include_inline
, part 1.
-
-
-
-
-
-
-
- Doc of T
, part 2.
-
-
-
-
-
-
-
- Doc of Include_inline_T'
, part 1.
-
-
-
-
-
-
-
-
- Doc of M'
from outside
-
-
-
-
-
-
-
- Doc of M''
, part 1.
-
-
-
-
-
-
-
class c1 : int => { ... }
-
-
-
- Doc of c1
, part 1.
-
-
-
-
-
-
class type ct = { ... }
-
-
-
- Doc of ct
, part 1.
-
-
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/module-type-Include_inline_T'/index.html b/test/html/expect/test_package+re/Toplevel_comments/module-type-Include_inline_T'/index.html
deleted file mode 100644
index f13d1700df..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/module-type-Include_inline_T'/index.html
+++ /dev/null
@@ -1,46 +0,0 @@
-
-
-
-
- Include_inline_T' (test_package+re.Toplevel_comments.Include_inline_T')
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » Include_inline_T'
-
-
-
- Module type Toplevel_comments.Include_inline_T'
-
-
- Doc of Include_inline_T'
, part 1.
-
-
- Doc of Include_inline_T'
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/module-type-Include_inline_T/index.html b/test/html/expect/test_package+re/Toplevel_comments/module-type-Include_inline_T/index.html
deleted file mode 100644
index d5f6651bc8..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/module-type-Include_inline_T/index.html
+++ /dev/null
@@ -1,38 +0,0 @@
-
-
-
-
- Include_inline_T (test_package+re.Toplevel_comments.Include_inline_T)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » Include_inline_T
-
-
-
- Module type Toplevel_comments.Include_inline_T
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Toplevel_comments/module-type-T/index.html b/test/html/expect/test_package+re/Toplevel_comments/module-type-T/index.html
deleted file mode 100644
index b008e3d1cb..0000000000
--- a/test/html/expect/test_package+re/Toplevel_comments/module-type-T/index.html
+++ /dev/null
@@ -1,39 +0,0 @@
-
-
-
-
- T (test_package+re.Toplevel_comments.T)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Toplevel_comments » T
-
-
-
- Module type Toplevel_comments.T
-
-
- Doc of T
, part 1.
-
-
- Doc of T
, part 2.
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Type/index.html b/test/html/expect/test_package+re/Type/index.html
deleted file mode 100644
index f24dd3ed12..0000000000
--- a/test/html/expect/test_package+re/Type/index.html
+++ /dev/null
@@ -1,555 +0,0 @@
-
-
-
-
- Type (test_package+re.Type)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Type
-
-
-
-
-
-
-
- Some documentation .
-
-
-
-
-
-
-
type private_ = pri int ;
-
-
-
-
-
type constructor('a) = 'a ;
-
-
-
-
-
type arrow = int => int ;
-
-
-
-
-
type higher_order = (int => int) => int ;
-
-
-
-
-
type labeled = l:int => int ;
-
-
-
-
-
type optional = ?l:int => int ;
-
-
-
-
-
type labeled_higher_order = (l:int => int) => (?l:int => int) => int ;
-
-
-
-
-
type pair = (int, int) ;
-
-
-
-
-
type parens_dropped = (int, int) ;
-
-
-
-
-
type triple = (int, int, int) ;
-
-
-
-
-
type nested_pair = ((int, int) , int) ;
-
-
-
-
-
-
-
type variant_e = {
-
-
} ;
-
-
-
-
-
type variant =
-
-
-
-
- | A
-
-
-
-
- | B (int)
-
-
-
-
- | C
-
-
-
-
- foo
-
-
-
-
-
-
- | D
-
-
-
-
- bar
-
-
-
-
-
-
- | E (variant_e )
-
-
-
-
-
;
-
-
-
-
-
type variant_c = {
-
-
} ;
-
-
-
-
-
-
type degenerate_gadt =
-
-
;
-
-
-
-
-
type private_variant = pri
-
-
;
-
-
-
-
-
type record = {
-
-
-
-
- a: int,
-
-
-
-
- mutable b: int,
-
-
-
-
- c: int,
-
-
-
-
- foo
-
-
-
-
-
-
- d: int,
-
-
-
-
- bar
-
-
-
-
-
-
- e: a. 'a ,
-
-
-
-
-
} ;
-
-
-
-
-
type polymorphic_variant = [
-
-
-
-
- |
`A
-
-
-
-
- |
`B(int)
-
-
-
-
- |
`C((int, unit) )
-
-
-
-
- |
`D
-
-
-
-
-
] ;
-
-
-
-
-
type polymorphic_variant_extension = [
-
-
] ;
-
-
-
-
-
type nested_polymorphic_variant = [
-
-
-
-
- |
`A([ `B | `C ] )
-
-
-
-
-
] ;
-
-
-
-
-
type private_extenion#row;
-
-
-
-
-
and private_extenion = pri [>
-
-
] ;
-
-
-
-
-
type object_ = {. a: int, b: int, c: int, } ;
-
-
-
-
-
module type X = { ... } ;
-
-
-
-
-
type module_ = (module X ) ;
-
-
-
-
-
type module_substitution = (module X with type t = int and type u = unit) ;
-
-
-
-
-
-
type contravariant(-'a);
-
-
-
-
-
type bivariant(_) = int ;
-
-
-
-
-
-
type using_binary = binary (int, int) ;
-
-
-
-
-
-
type constrained('a) = 'a constraint 'a = int ;
-
-
-
-
-
type exact_variant('a) = 'a constraint 'a = [ `A | `B (int) ] ;
-
-
-
-
-
type lower_variant('a) = 'a constraint 'a = [> `A | `B (int) ] ;
-
-
-
-
-
type any_variant('a) = 'a constraint 'a = [> ] ;
-
-
-
-
-
type upper_variant('a) = 'a constraint 'a = [< `A | `B (int) ] ;
-
-
-
-
-
-
type exact_object('a) = 'a constraint 'a = {. a: int, b: int, } ;
-
-
-
-
-
type lower_object('a) = 'a constraint 'a = {.. a: int, b: int, } ;
-
-
-
-
-
type poly_object('a) = 'a constraint 'a = {. a: a. 'a , } ;
-
-
-
-
-
type double_constrained('a, 'b) = ('a , 'b ) constraint 'a = int constraint 'b = unit ;
-
-
-
-
-
type as_ = (int as 'a, 'a ) ;
-
-
-
-
-
type extensible = .. ;
-
-
-
-
-
type extensible +=
-
-
-
-
- | Extension
-
-
-
-
- Documentation for Extension
.
-
-
-
-
-
-
- | Another_extension
-
-
-
-
- Documentation for Another_extension
.
-
-
-
-
-
-
-
;
-
-
-
-
-
type mutually =
-
-
;
-
-
-
-
-
and recursive =
-
-
;
-
-
-
-
-
exception Foo (int, int);
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/Val/index.html b/test/html/expect/test_package+re/Val/index.html
deleted file mode 100644
index e38127e88c..0000000000
--- a/test/html/expect/test_package+re/Val/index.html
+++ /dev/null
@@ -1,53 +0,0 @@
-
-
-
-
- Val (test_package+re.Val)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » Val
-
-
-
-
-
-
let documented: unit;
-
-
-
-
-
-
let undocumented: unit;
-
-
-
-
-
let documented_above: unit;
-
-
-
-
-
-
diff --git a/test/html/expect/test_package+re/mld.html b/test/html/expect/test_package+re/mld.html
deleted file mode 100644
index 04af7d66cc..0000000000
--- a/test/html/expect/test_package+re/mld.html
+++ /dev/null
@@ -1,94 +0,0 @@
-
-
-
-
- mld (test_package+re.mld)
-
-
-
-
-
-
-
-
-
-
- Up – test_package+re » mld
-
-
-
- Mld Page
-
-
- This is an .mld
file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do.
-
-
- It will have a TOC generated from section headings.
-
-
-
-
-
-
-
- Section
-
-
- This is a section.
-
-
- Another paragraph in section.
-
-
- Another section
-
-
- This is another section.
-
-
- Another paragraph in section 2.
-
-
- Subsection
-
-
- This is a subsection.
-
-
- Another paragraph in subsection.
-
-
- Yet another paragraph in subsection.
-
-
- Another Subsection
-
-
- This is another subsection.
-
-
- Another paragraph in subsection 2.
-
-
- Yet another paragraph in subsection 2.
-
-
-
-
diff --git a/test/html/test.ml b/test/html/test.ml
deleted file mode 100644
index c4d92d3e70..0000000000
--- a/test/html/test.ml
+++ /dev/null
@@ -1,350 +0,0 @@
-open Printf
-
-(* Utils *)
-
-let ( // ) = Filename.concat
-
-let command label =
- Printf.ksprintf (fun s ->
- let exit_code = Sys.command s in
- if exit_code <> 0 then
- Alcotest.failf "'%s' exited with %i" label exit_code)
-
-(* Filename.extension is only available on 4.04. *)
-module Filename = struct
- include Filename
-
- let extension filename =
- let dot_index = String.rindex filename '.' in
- String.sub filename dot_index (String.length filename - dot_index)
-end
-
-(* Testing environment *)
-
-module Env = struct
- let package = "test_package"
-
- let odoc = "../../src/odoc/bin/main.exe"
-
- let path ?(from_root = false) = function
- | `scratch when from_root -> "_build/default/test/html/_scratch"
- | `scratch -> "_scratch"
- | `expect when from_root -> "test/html/expect"
- | `expect -> "expect"
- | `cases when from_root -> "test/cases"
- | `cases -> "../cases"
-
- let running_in_travis_tidy_row =
- match (Sys.getenv "TRAVIS", Sys.getenv "TIDY") with
- | "true", "YES" -> true
- | _ -> false
- | exception Not_found -> false
-
- let init () =
- if running_in_travis_tidy_row && not Tidy.is_present_in_path then
- Alcotest.failf "Could not find `tidy` in $PATH in a CI environment";
-
- Unix.mkdir (path `scratch) 0o755
-end
-
-(* Test case type and helpers *)
-
-(* A test case is a description of an input source file with a specific set of
- options to be tested. Each test case results in a unique generated output to
- be compared with an actually produced one.
-
- All paths defined in this module are relative to the build directory. *)
-module Case = struct
- type t = {
- name : string;
- kind : [ `mli | `mld | `ml ];
- theme_uri : string option;
- syntax : [ `ml | `re ];
- outputs : string list;
- }
-
- let make ?theme_uri ?(syntax = `ml) (input, outputs) =
- let name = Filename.chop_extension input in
- let kind =
- match Filename.extension input with
- | ".mli" -> `mli
- | ".mld" -> `mld
- | ".ml" -> `ml
- | _ ->
- invalid_arg (sprintf "Expected mli, mld, or ml files, got %s" input)
- in
- { name; kind; theme_uri; syntax; outputs }
-
- let name case = case.name
-
- let kind case = case.kind
-
- let theme_uri case = case.theme_uri
-
- let string_of_syntax = function `re -> "re" | `ml -> "ml"
-
- (* The package name is enriched with test case options. *)
- let package case =
- let opts = [ string_of_syntax case.syntax ] in
- let opts =
- match case.theme_uri with
- | Some _ -> "custom_theme" :: opts
- | None -> opts
- in
- let opts = String.concat "," (List.sort compare opts) in
- Env.package ^ "+" ^ opts
-
- let cmi_file case = Env.path `scratch // (case.name ^ ".cmi")
-
- let cmti_file case = Env.path `scratch // (case.name ^ ".cmti")
-
- let cmo_file case = Env.path `scratch // (case.name ^ ".cmo")
-
- let cmt_file case = Env.path `scratch // (case.name ^ ".cmt")
-
- let odoc_file case =
- match case.kind with
- | `mli | `ml -> Env.path `scratch // (case.name ^ ".odoc")
- | `mld -> Env.path `scratch // ("page-" ^ case.name ^ ".odoc")
-
- let source_file case =
- match case.kind with
- | `mli -> (Env.path `cases // case.name) ^ ".mli"
- | `mld -> (Env.path `cases // case.name) ^ ".mld"
- | `ml -> (Env.path `cases // case.name) ^ ".ml"
-
- let outputs case = List.map (fun o -> package case // o) case.outputs
-end
-
-let pretty_print_html_in_place html_file =
- let temporary_pretty_printed_file = html_file ^ ".pretty" in
- let html_stream, close_html_file = Markup.file html_file in
-
- html_stream |> Markup.parse_html |> Markup.signals |> Markup.pretty_print
- |> Markup.write_html
- |> Markup.to_file temporary_pretty_printed_file;
-
- close_html_file ();
-
- Sys.rename temporary_pretty_printed_file html_file
-
-let generate_html case =
- let theme_uri_option =
- match Case.theme_uri case with
- | Some theme_uri -> "--theme-uri=" ^ theme_uri
- | None -> ""
- in
- match Case.kind case with
- | `mli ->
- command "ocamlfind c" "ocamlfind c -bin-annot -o %s -c %s"
- (Case.cmi_file case) (Case.source_file case);
-
- command "odoc compile" "%s compile --package=%s %s" Env.odoc
- (Case.package case) (Case.cmti_file case);
-
- command "odoc html" "%s html %s --syntax=%s --output-dir=%s %s" Env.odoc
- theme_uri_option
- (Case.string_of_syntax case.syntax)
- (Env.path `scratch)
- (Case.odoc_file case)
- | `mld ->
- command "odoc compile" "%s compile --package=%s -o %s %s" Env.odoc
- (Case.package case) (Case.odoc_file case) (Case.source_file case);
-
- command "odoc html" "%s html %s --output-dir=%s %s" Env.odoc
- theme_uri_option
- (Env.path `scratch)
- (Case.odoc_file case)
- | `ml ->
- command "ocamlfind c" "ocamlfind c -bin-annot -o %s -c %s"
- (Case.cmo_file case) (Case.source_file case);
-
- command "odoc compile" "%s compile --package=%s %s" Env.odoc
- (Case.package case) (Case.cmt_file case);
-
- command "odoc html" "%s html %s --syntax=%s --output-dir=%s %s" Env.odoc
- theme_uri_option
- (Case.string_of_syntax case.syntax)
- (Env.path `scratch)
- (Case.odoc_file case)
-
-let diff =
- (* Alcotest will run all tests. We need to know when something fails for the
- first time to stop diffing and generating promotion files. *)
- let already_failed = ref false in
- fun output ->
- let actual_file = Env.path `scratch // output in
- let expected_file = Env.path `expect // output in
- let cmd = sprintf "diff -N -u -b %S %S" expected_file actual_file in
- match Sys.command cmd with
- | 0 -> ()
- | 1 when !already_failed ->
- (* Don't run diff for other failing tests as only one at time is shown. *)
- Alcotest.fail "generated HTML should match expected"
- | 1 ->
- (* If the diff command exits with 1, the two HTML files are different.
- diff has already written its output to STDOUT.
-
- Also provide the command for overwriting the expected output with the
- actual output, in case it is the actual output that is correct.
- The paths are defined relative to the project's root. *)
- let root_actual_file = Env.path `scratch ~from_root:true // output in
- let root_expected_file = Env.path `expect ~from_root:true // output in
- let write_file filename data =
- Markup.string data |> Markup.to_file filename
- in
- write_file Env.(path `scratch // "actual") root_actual_file;
- write_file Env.(path `scratch // "expected") root_expected_file;
-
- prerr_endline "\nTo promote the actual output to expected, run:";
- prerr_endline "make promote-html && make test\n";
-
- already_failed := true;
- Alcotest.fail "generated HTML should match expected"
- | exit_code -> Alcotest.failf "'diff' exited with %i" exit_code
-
-(* Actual Tests *)
-
-let output_support_files =
- let run () =
- command "odoc support-files" "%s support-files --output-dir %s" Env.odoc
- (Env.path `scratch)
- in
- ("support-files", `Slow, run)
-
-let make_test_case ?theme_uri ?syntax case =
- let case = Case.make ?theme_uri ?syntax case in
- let run () =
- (* Compile the source file and generate HTML. *)
- generate_html case;
-
- List.iter
- (fun output ->
- let actual_file = Env.path `scratch // output in
-
- if Sys.file_exists actual_file then (
- (* Pretty-print output HTML for better diffing. *)
- pretty_print_html_in_place actual_file;
-
- (* Run HTML validation on output files. *)
- if Tidy.is_present_in_path then
- let issues = Tidy.validate actual_file in
- if issues <> [] then (
- List.iter prerr_endline issues;
- Alcotest.fail "Tidy validation error"));
-
- (* Diff the actual outputs with the expected outputs. *)
- diff output)
- (Case.outputs case)
- in
- (Case.name case, `Slow, run)
-
-let make_input file sub_modules =
- let base = Astring.String.Ascii.capitalize (Filename.chop_extension file) in
- let index p = String.concat Filename.dir_sep (p @ [ "index.html" ]) in
- (file, index [ base ] :: List.map (fun m -> index [ base; m ]) sub_modules)
-
-let source_files_all =
- [
- ("val.mli", [ "Val/index.html" ]);
- ("markup.mli", [ "Markup/index.html" ]);
- ("section.mli", [ "Section/index.html" ]);
- ("module.mli", [ "Module/index.html" ]);
- ("interlude.mli", [ "Interlude/index.html" ]);
- ("include.mli", [ "Include/index.html" ]);
- make_input "include2.ml" [ "Y_include_synopsis"; "Y_include_doc" ];
- ( "include_sections.mli",
- [
- "Include_sections/index.html";
- "Include_sections/module-type-Something/index.html";
- ] );
- ("mld.mld", [ "mld.html" ]);
- ( "nested.mli",
- [
- "Nested/index.html";
- "Nested/F/index.html";
- "Nested/F/argument-1-Arg1/index.html";
- "Nested/F/argument-2-Arg2/index.html";
- "Nested/X/index.html";
- "Nested/class-z/index.html";
- "Nested/class-inherits/index.html";
- "Nested/module-type-Y/index.html";
- ] );
- ("ocamlary.mli", [ "Ocamlary/index.html" ]);
- ("type.mli", [ "Type/index.html" ]);
- ("external.mli", [ "External/index.html" ]);
- ("functor.mli", [ "Functor/index.html" ]);
- ("class.mli", [ "Class/index.html" ]);
- ("stop.mli", [ "Stop/index.html" ]);
- ("bugs.ml", [ "Bugs/index.html" ]);
- ("alias.ml", [ "Alias/index.html"; "Alias/X/index.html" ]);
- make_input "toplevel_comments.mli"
- [
- "module-type-T";
- "Include_inline";
- "Include_inline'";
- "module-type-Include_inline_T";
- "module-type-Include_inline_T'";
- "M";
- "M'";
- "M''";
- "Alias";
- "class-c1";
- "class-type-ct";
- "class-c2";
- "Ref_in_synopsis";
- ];
- ]
-
-let source_files_post406 =
- [ ("bugs_post_406.mli", [ "Bugs_post_406/index.html" ]) ]
-
-let source_files_post408 =
- [
- ("recent.mli", [ "Recent/index.html"; "Recent/X/index.html" ]);
- ("recent_impl.ml", [ "Recent_impl/index.html" ]);
- ("labels.mli", [ "Labels/index.html" ]);
- ]
-
-let source_files_pre410 = [ ("bugs_pre_410.ml", [ "Bugs_pre_410/index.html" ]) ]
-
-let source_files_post404 =
- [ ("stop_dead_link_doc.mli", [ "Stop_dead_link_doc/index.html" ]) ]
-
-let source_files =
- let cur =
- Astring.String.cuts ~sep:"." Sys.ocaml_version
- |> List.map (fun i -> try Some (int_of_string i) with _ -> None)
- in
- match cur with
- | Some major :: Some minor :: _ ->
- List.concat
- [
- (if major = 4 && minor < 10 then source_files_pre410 else []);
- (if major = 4 && minor > 8 then source_files_post408 else []);
- (if major = 4 && minor >= 6 then source_files_post406 else []);
- (if major = 4 && minor >= 4 then source_files_post404 else []);
- source_files_all;
- ]
- | _ -> source_files_all
-
-let () =
- Env.init ();
-
- Alcotest.run "html"
- [
- ("support_files", [ output_support_files ]);
- ("html_ml", List.map (make_test_case ~syntax:`ml) source_files);
- ("html_re", List.map (make_test_case ~syntax:`re) source_files);
- ( "custom_theme",
- [
- make_test_case ~theme_uri:"/a/b/c"
- ("module.mli", [ "Module/index.html" ]);
- make_test_case ~theme_uri:"https://foo.com/a/b/c/"
- ("val.mli", [ "Val/index.html" ]);
- make_test_case ~theme_uri:"../b/c"
- ("include.mli", [ "Include/index.html" ]);
- make_test_case ~theme_uri:"b/c"
- ("section.mli", [ "Section/index.html" ]);
- ] );
- ]
diff --git a/test/html/tidy.ml b/test/html/tidy.ml
deleted file mode 100644
index 875d9b5e97..0000000000
--- a/test/html/tidy.ml
+++ /dev/null
@@ -1,55 +0,0 @@
-let muted_warnings =
- [
- (* NOTE: see https://github.com/ocaml/odoc/issues/188 *)
- "NESTED_EMPHASIS";
- (* NOTE: see https://github.com/ocaml/odoc/pull/185#discussion_r217906131 *)
- "MISSING_STARTTAG";
- "DISCARDING_UNEXPECTED";
- (* NOTE: see https://github.com/ocaml/odoc/issues/186 *)
- "ANCHOR_NOT_UNIQUE";
- "TRIM_EMPTY_ELEMENT";
- ]
-
-let is_present_in_path =
- Sys.command "which tidy > /dev/null" = 0
- && Sys.command "tidy -show-config < /dev/null | grep '^mute' > /dev/null" = 0
-
-(* Returns a list of errors and warnings. *)
-let validate file =
- if not (Sys.file_exists file) then
- invalid_arg ("tidy: file `" ^ file ^ "` does not exist");
- let muted_warnings = String.concat "," muted_warnings in
- let options =
- String.concat " "
- [
- "-quiet";
- "--mute " ^ muted_warnings;
- "--mute-id yes";
- "--show-errors 200";
- "-errors";
- "-ashtml";
- ]
- in
- let cmd = Printf.sprintf "tidy %s %S" options file in
- let ((_, _, stderr) as proc) = Unix.open_process_full cmd [||] in
-
- let errors_and_warnings =
- let rec loop acc =
- match input_line stderr with
- | message -> loop (message :: acc)
- | exception End_of_file -> List.rev acc
- in
- loop []
- in
-
- match Unix.close_process_full proc with
- (* All input files were processed successfully. *)
- | WEXITED 0 -> []
- (* There were warnings. *)
- | WEXITED 1
- (* There were errors. *)
- | WEXITED 2 ->
- errors_and_warnings
- | _ ->
- let msg = "Unexpected process termination while running: " ^ cmd in
- raise (Failure msg)
diff --git a/test/latex/dune b/test/latex/dune
deleted file mode 100644
index 0ddf0a06f1..0000000000
--- a/test/latex/dune
+++ /dev/null
@@ -1,13 +0,0 @@
-(executable
- (name test)
- (libraries alcotest))
-
-(rule
- (alias runtest)
- (action
- (run %{exe:test.exe}))
- (deps
- test.exe
- %{workspace_root}/src/odoc/bin/main.exe
- (source_tree ../cases)
- (source_tree expect)))
diff --git a/test/latex/expect/test_package+ml/Alias.X.tex b/test/latex/expect/test_package+ml/Alias.X.tex
deleted file mode 100644
index 5ea5dbbf83..0000000000
--- a/test/latex/expect/test_package+ml/Alias.X.tex
+++ /dev/null
@@ -1,5 +0,0 @@
-\section{Module \ocamlinlinecode{Alias.\allowbreak{}X}}\label{container-page-test+u+package+++ml-module-Alias-module-X}%
-\label{container-page-test+u+package+++ml-module-Alias-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}%
-\medbreak
-
-
diff --git a/test/latex/expect/test_package+ml/Alias.tex b/test/latex/expect/test_package+ml/Alias.tex
deleted file mode 100644
index 0f3d73254b..0000000000
--- a/test/latex/expect/test_package+ml/Alias.tex
+++ /dev/null
@@ -1,8 +0,0 @@
-\section{Module \ocamlinlinecode{Alias}}\label{container-page-test+u+package+++ml-module-Alias}%
-\label{container-page-test+u+package+++ml-module-Alias-module-Foo+u++u+X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Alias-module-Foo+u++u+X]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Alias-module-Foo+u++u+X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[xref-unresolved]{\ocamlinlinecode{int}}}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}%
-\medbreak
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Alias-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
-
-\input{test_package+ml/Alias.X.tex}
diff --git a/test/latex/expect/test_package+ml/Bugs.tex b/test/latex/expect/test_package+ml/Bugs.tex
deleted file mode 100644
index af6bd81060..0000000000
--- a/test/latex/expect/test_package+ml/Bugs.tex
+++ /dev/null
@@ -1,6 +0,0 @@
-\section{Module \ocamlinlinecode{Bugs}}\label{container-page-test+u+package+++ml-module-Bugs}%
-\label{container-page-test+u+package+++ml-module-Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\
-\label{container-page-test+u+package+++ml-module-Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : ?bar:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}%
-\medbreak
-
-
diff --git a/test/latex/expect/test_package+ml/Bugs_pre_410.tex b/test/latex/expect/test_package+ml/Bugs_pre_410.tex
deleted file mode 100644
index bc39f1ac93..0000000000
--- a/test/latex/expect/test_package+ml/Bugs_pre_410.tex
+++ /dev/null
@@ -1,6 +0,0 @@
-\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}pre\_\allowbreak{}410}}\label{container-page-test+u+package+++ml-module-Bugs+u+pre+u+410}%
-\label{container-page-test+u+package+++ml-module-Bugs+u+pre+u+410-type-opt'}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt' = int option}\\
-\label{container-page-test+u+package+++ml-module-Bugs+u+pre+u+410-val-foo'}\ocamlcodefragment{\ocamltag{keyword}{val} foo' : ?bar:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Similar to \ocamlinlinecode{Bugs}, but the printed type of \ocamlinlinecode{\textasciitilde{}bar} should be \ocamlinlinecode{int}, not \ocamlinlinecode{'a}. This probably requires fixing in the compiler. See \href{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}\footnote{\url{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}}.\end{ocamlindent}%
-\medbreak
-
-
diff --git a/test/latex/expect/test_package+ml/Class.empty_virtual'.tex b/test/latex/expect/test_package+ml/Class.empty_virtual'.tex
deleted file mode 100644
index c4b6dcf937..0000000000
--- a/test/latex/expect/test_package+ml/Class.empty_virtual'.tex
+++ /dev/null
@@ -1,3 +0,0 @@
-\section{Class \ocamlinlinecode{Class.\allowbreak{}empty\_\allowbreak{}virtual'}}\label{package-test+u+package+++ml-module-Class-class-empty+u+virtual'}%
-
-
diff --git a/test/latex/expect/test_package+ml/Class.polymorphic'.tex b/test/latex/expect/test_package+ml/Class.polymorphic'.tex
deleted file mode 100644
index a470185953..0000000000
--- a/test/latex/expect/test_package+ml/Class.polymorphic'.tex
+++ /dev/null
@@ -1,3 +0,0 @@
-\section{Class \ocamlinlinecode{Class.\allowbreak{}polymorphic'}}\label{package-test+u+package+++ml-module-Class-class-polymorphic'}%
-
-
diff --git a/test/latex/expect/test_package+ml/Class.tex b/test/latex/expect/test_package+ml/Class.tex
deleted file mode 100644
index 832b2f1648..0000000000
--- a/test/latex/expect/test_package+ml/Class.tex
+++ /dev/null
@@ -1,20 +0,0 @@
-\section{Module \ocamlinlinecode{Class}}\label{container-page-test+u+package+++ml-module-Class}%
-\label{container-page-test+u+package+++ml-module-Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test+u+package+++ml-module-Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[container-page-test+u+package+++ml-module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[container-page-test+u+package+++ml-module-Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[container-page-test+u+package+++ml-module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-type-empty+u+virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[container-page-test+u+package+++ml-module-Class-class-type-empty+u+virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-empty+u+virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[container-page-test+u+package+++ml-module-Class-class-empty+u+virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[container-page-test+u+package+++ml-module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-type-polymorphic}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} 'a \hyperref[container-page-test+u+package+++ml-module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Class-class-polymorphic'}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[container-page-test+u+package+++ml-module-Class-class-polymorphic']{\ocamlinlinecode{polymorphic'}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \hyperref[container-page-test+u+package+++ml-module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\\
-
-\input{test_package+ml/Class.mutually'.tex}
-\input{test_package+ml/Class.recursive'.tex}
-\input{test_package+ml/Class.empty_virtual'.tex}
-\input{test_package+ml/Class.polymorphic'.tex}
diff --git a/test/latex/expect/test_package+ml/External.tex b/test/latex/expect/test_package+ml/External.tex
deleted file mode 100644
index ac2aa12276..0000000000
--- a/test/latex/expect/test_package+ml/External.tex
+++ /dev/null
@@ -1,5 +0,0 @@
-\section{Module \ocamlinlinecode{External}}\label{container-page-test+u+package+++ml-module-External}%
-\label{container-page-test+u+package+++ml-module-External-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Foo \emph{bar}.\end{ocamlindent}%
-\medbreak
-
-
diff --git a/test/latex/expect/test_package+ml/Functor.F1.tex b/test/latex/expect/test_package+ml/Functor.F1.tex
deleted file mode 100644
index 9d021aaf46..0000000000
--- a/test/latex/expect/test_package+ml/Functor.F1.tex
+++ /dev/null
@@ -1,9 +0,0 @@
-\section{Module \ocamlinlinecode{Functor.\allowbreak{}F1}}\label{container-page-test+u+package+++ml-module-Functor-module-F1}%
-\subsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Functor.F2.tex b/test/latex/expect/test_package+ml/Functor.F2.tex
deleted file mode 100644
index 7b21a4b02e..0000000000
--- a/test/latex/expect/test_package+ml/Functor.F2.tex
+++ /dev/null
@@ -1,9 +0,0 @@
-\section{Module \ocamlinlinecode{Functor.\allowbreak{}F2}}\label{container-page-test+u+package+++ml-module-Functor-module-F2}%
-\subsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Functor.F3.tex b/test/latex/expect/test_package+ml/Functor.F3.tex
deleted file mode 100644
index e7d6c0c257..0000000000
--- a/test/latex/expect/test_package+ml/Functor.F3.tex
+++ /dev/null
@@ -1,9 +0,0 @@
-\section{Module \ocamlinlinecode{Functor.\allowbreak{}F3}}\label{container-page-test+u+package+++ml-module-Functor-module-F3}%
-\subsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Functor.F4.tex b/test/latex/expect/test_package+ml/Functor.F4.tex
deleted file mode 100644
index 09cd821fa4..0000000000
--- a/test/latex/expect/test_package+ml/Functor.F4.tex
+++ /dev/null
@@ -1,9 +0,0 @@
-\section{Module \ocamlinlinecode{Functor.\allowbreak{}F4}}\label{container-page-test+u+package+++ml-module-Functor-module-F4}%
-\subsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-F4-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Functor.F5.tex b/test/latex/expect/test_package+ml/Functor.F5.tex
deleted file mode 100644
index 54dd46e75e..0000000000
--- a/test/latex/expect/test_package+ml/Functor.F5.tex
+++ /dev/null
@@ -1,6 +0,0 @@
-\section{Module \ocamlinlinecode{Functor.\allowbreak{}F5}}\label{package-test+u+package+++ml-module-Functor-module-F5}%
-\subsection{Parameters\label{parameters}}%
-\subsection{Signature\label{signature}}%
-\label{package-test+u+package+++ml-module-Functor-module-F5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Functor.tex b/test/latex/expect/test_package+ml/Functor.tex
deleted file mode 100644
index cedf90f237..0000000000
--- a/test/latex/expect/test_package+ml/Functor.tex
+++ /dev/null
@@ -1,23 +0,0 @@
-\section{Module \ocamlinlinecode{Functor}}\label{container-page-test+u+package+++ml-module-Functor}%
-\label{container-page-test+u+package+++ml-module-Functor-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Functor-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Functor-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsubsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Functor-module-type-S1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Functor-module-F1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F1]{\ocamlinlinecode{F1}}}\ocamlcodefragment{ (\hyperref[container-page-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\
-\label{container-page-test+u+package+++ml-module-Functor-module-F2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F2]{\ocamlinlinecode{F2}}}\ocamlcodefragment{ (\hyperref[container-page-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S-type-t]{\ocamlinlinecode{t}} = \hyperref[container-page-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\
-\label{container-page-test+u+package+++ml-module-Functor-module-F3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F3]{\ocamlinlinecode{F3}}}\ocamlcodefragment{ (\hyperref[container-page-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Functor-module-F4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F4]{\ocamlinlinecode{F4}}}\ocamlcodefragment{ (\hyperref[container-page-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\
-\label{container-page-test+u+package+++ml-module-Functor-module-F5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Functor-module-F5]{\ocamlinlinecode{F5}}}\ocamlcodefragment{ () : \hyperref[container-page-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\
-
-\input{test_package+ml/Functor.F1.tex}
-\input{test_package+ml/Functor.F2.tex}
-\input{test_package+ml/Functor.F3.tex}
-\input{test_package+ml/Functor.F4.tex}
-\input{test_package+ml/Functor.F5.tex}
diff --git a/test/latex/expect/test_package+ml/Include.tex b/test/latex/expect/test_package+ml/Include.tex
deleted file mode 100644
index 779f37f468..0000000000
--- a/test/latex/expect/test_package+ml/Include.tex
+++ /dev/null
@@ -1,29 +0,0 @@
-\section{Module \ocamlinlinecode{Include}}\label{container-page-test+u+package+++ml-module-Include}%
-\label{container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}\label{container-page-test+u+package+++ml-module-Include-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Include-module-type-Inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include-module-type-Inlined-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}\label{container-page-test+u+package+++ml-module-Include-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}\label{container-page-test+u+package+++ml-module-Include-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\
-\label{container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}\label{container-page-test+u+package+++ml-module-Include-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\
-\label{container-page-test+u+package+++ml-module-Include-module-type-Inherent+u+Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include-module-type-Inherent+u+Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test+u+package+++ml-module-Include-type-t]{\ocamlinlinecode{t}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{container-page-test+u+package+++ml-module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test+u+package+++ml-module-Include-type-t]{\ocamlinlinecode{t}}}\\
-\label{container-page-test+u+package+++ml-module-Include-module-type-Dorminant+u+Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Dorminant+u+Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{container-page-test+u+package+++ml-module-Include-module-type-Dorminant+u+Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test+u+package+++ml-module-Include-type-t]{\ocamlinlinecode{t}}}\\
-\label{container-page-test+u+package+++ml-module-Include-module-type-Dorminant+u+Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test+u+package+++ml-module-Include-type-u]{\ocamlinlinecode{u}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Dorminant+u+Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include-module-type-Inherent+u+Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{container-page-test+u+package+++ml-module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test+u+package+++ml-module-Include-type-t]{\ocamlinlinecode{t}}}\\
-\label{container-page-test+u+package+++ml-module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[container-page-test+u+package+++ml-module-Include-type-u]{\ocamlinlinecode{u}}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Include2.tex b/test/latex/expect/test_package+ml/Include2.tex
deleted file mode 100644
index a9ec877b6d..0000000000
--- a/test/latex/expect/test_package+ml/Include2.tex
+++ /dev/null
@@ -1,21 +0,0 @@
-\section{Module \ocamlinlinecode{Include2}}\label{container-page-test+u+package+++ml-module-Include2}%
-\label{container-page-test+u+package+++ml-module-Include2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Include2-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include2-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Comment about X that should not appear when including X below.\end{ocamlindent}%
-\medbreak
-\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include2-module-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{end}Comment about X that should not appear when including X below.
-
-\label{container-page-test+u+package+++ml-module-Include2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
-\label{container-page-test+u+package+++ml-module-Include2-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include2-module-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment of Y.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Include2-module-Y+u+include+u+synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y+u+include+u+synopsis]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{container-page-test+u+package+++ml-module-Include2-module-Y+u+include+u+synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}The \ocamlinlinecode{include Y} below should have the synopsis from \ocamlinlinecode{Y}'s top-comment attached to it.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Include2-module-Y+u+include+u+doc}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y+u+include+u+doc]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}doc}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}Doc attached to \ocamlinlinecode{include Y}. \ocamlinlinecode{Y}'s top-comment shouldn't appear here.\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{container-page-test+u+package+++ml-module-Include2-module-Y+u+include+u+doc-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test+u+package+++ml-module-Include2-module-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Include_sections.tex b/test/latex/expect/test_package+ml/Include_sections.tex
deleted file mode 100644
index c7afe47e56..0000000000
--- a/test/latex/expect/test_package+ml/Include_sections.tex
+++ /dev/null
@@ -1,71 +0,0 @@
-\section{Module \ocamlinlinecode{Include\_\allowbreak{}sections}}\label{container-page-test+u+package+++ml-module-Include+u+sections}%
-\label{container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
-\subsubsection{Something 1\label{something-1}}%
-foo
-
-\label{container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
-\subsubsection{Something 2\label{something-2}}%
-\label{container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
-\medbreak
-\subsubsection{Something 1-bis\label{something-1-bis}}%
-Some text.
-
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A module type.\end{ocamlindent}%
-\medbreak
-Let's include \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something}]} once
-
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
-\subsection{Something 1\label{something-1}}%
-foo
-
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
-\subsubsection{Something 2\label{something-2}}%
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
-\medbreak
-\subsection{Something 1-bis\label{something-1-bis}}%
-Some text.
-
-\subsection{Second include\label{second-include}}%
-Let's include \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something}]} a second time: the heading level should be shift here.
-
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
-\subsection{Something 1\label{something-1}}%
-foo
-
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
-\subsubsection{Something 2\label{something-2}}%
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
-\medbreak
-\subsection{Something 1-bis\label{something-1-bis}}%
-Some text.
-
-\subsubsection{Third include\label{third-include}}%
-Shifted some more.
-
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
-\subsection{Something 1\label{something-1}}%
-foo
-
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
-\subsubsection{Something 2\label{something-2}}%
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
-\medbreak
-\subsection{Something 1-bis\label{something-1-bis}}%
-Some text.
-
-And let's include it again, but without inlining it this time: the ToC shouldn't grow.
-
-\ocamltag{keyword}{include} \hyperref[container-page-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{container-page-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\
-\subsection{Something 1\label{something-1}}%
-foo
-
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\
-\subsubsection{Something 2\label{something-2}}%
-\label{container-page-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}%
-\medbreak
-\subsection{Something 1-bis\label{something-1-bis}}%
-Some text.
-
-
-
diff --git a/test/latex/expect/test_package+ml/Interlude.tex b/test/latex/expect/test_package+ml/Interlude.tex
deleted file mode 100644
index fa965deb78..0000000000
--- a/test/latex/expect/test_package+ml/Interlude.tex
+++ /dev/null
@@ -1,22 +0,0 @@
-\section{Module \ocamlinlinecode{Interlude}}\label{container-page-test+u+package+++ml-module-Interlude}%
-This is the comment associated to the module.
-
-Some separate stray text at the top of the module.
-
-\label{container-page-test+u+package+++ml-module-Interlude-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Foo.\end{ocamlindent}%
-\medbreak
-Some stray text that is not associated with any signature item.
-
-It has multiple paragraphs.
-
-A separate block of stray text, adjacent to the preceding one.
-
-\label{container-page-test+u+package+++ml-module-Interlude-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}Bar.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Interlude-val-multiple}\ocamlcodefragment{\ocamltag{keyword}{val} multiple : unit}\\
-\label{container-page-test+u+package+++ml-module-Interlude-val-signature}\ocamlcodefragment{\ocamltag{keyword}{val} signature : unit}\\
-\label{container-page-test+u+package+++ml-module-Interlude-val-items}\ocamlcodefragment{\ocamltag{keyword}{val} items : unit}\\
-Stray text at the bottom of the module.
-
-
-
diff --git a/test/latex/expect/test_package+ml/Module.tex b/test/latex/expect/test_package+ml/Module.tex
deleted file mode 100644
index 2eb9526284..0000000000
--- a/test/latex/expect/test_package+ml/Module.tex
+++ /dev/null
@@ -1,75 +0,0 @@
-\section{Module \ocamlinlinecode{Module}}\label{container-page-test+u+package+++ml-module-Module}%
-Foo.
-
-\label{container-page-test+u+package+++ml-module-Module-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See \href{https://caml.inria.fr/mantis/view.php?id=7701}{https://caml.inria.fr/mantis/view.php?id=7701}\footnote{\url{https://caml.inria.fr/mantis/view.php?id=7701}}.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Module-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S1}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S2]{\ocamlinlinecode{S2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S2-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S2-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S2-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S2-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S3}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S3]{\ocamlinlinecode{S3}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S3-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = string}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S3-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S3-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S3-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S4}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S4]{\ocamlinlinecode{S4}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S4-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S4-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S4-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S4-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S4-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S5}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S5]{\ocamlinlinecode{S5}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S5-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S5-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S5-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S5-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-type-result}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) result}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S6}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S6]{\ocamlinlinecode{S6}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S6-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S6-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S6-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S6-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S6-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S7}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S7]{\ocamlinlinecode{S7}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S7-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S7-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S7-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S7-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[container-page-test+u+package+++ml-module-Module-module-M']{\ocamlinlinecode{M'}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S8]{\ocamlinlinecode{S8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Module-module-type-S8-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S8-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S8-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S8-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-type-S9}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Module-module-type-S9]{\ocamlinlinecode{S9}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-Mutually}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-Mutually]{\ocamlinlinecode{Mutually}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Module-module-Recursive}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Module-module-Recursive]{\ocamlinlinecode{Recursive}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Nested.F.tex b/test/latex/expect/test_package+ml/Nested.F.tex
deleted file mode 100644
index 05dfd813da..0000000000
--- a/test/latex/expect/test_package+ml/Nested.F.tex
+++ /dev/null
@@ -1,25 +0,0 @@
-\section{Module \ocamlinlinecode{Nested.\allowbreak{}F}}\label{container-page-test+u+package+++ml-module-Nested-module-F}%
-This is a functor F.
-
-Some additional comments.
-
-\subsection{Type\label{type}}%
-\subsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
-\medbreak
-\subsubsection{Values\label{values}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}%
-\medbreak
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
-\medbreak
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{Arg1.\allowbreak{}t}} * \hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2-type-t]{\ocamlinlinecode{Arg2.\allowbreak{}t}}}\begin{ocamlindent}Some type.\end{ocamlindent}%
-\medbreak
-
-
diff --git a/test/latex/expect/test_package+ml/Nested.inherits.tex b/test/latex/expect/test_package+ml/Nested.inherits.tex
deleted file mode 100644
index 1d5fdda365..0000000000
--- a/test/latex/expect/test_package+ml/Nested.inherits.tex
+++ /dev/null
@@ -1,4 +0,0 @@
-\section{Class \ocamlinlinecode{Nested.\allowbreak{}inherits}}\label{container-page-test+u+package+++ml-module-Nested-class-inherits}%
-\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[container-page-test+u+package+++ml-module-Nested-class-z]{\ocamlinlinecode{z}}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Nested.tex b/test/latex/expect/test_package+ml/Nested.tex
deleted file mode 100644
index 318323a465..0000000000
--- a/test/latex/expect/test_package+ml/Nested.tex
+++ /dev/null
@@ -1,34 +0,0 @@
-\section{Module \ocamlinlinecode{Nested}}\label{container-page-test+u+package+++ml-module-Nested}%
-This comment needs to be here before \#235 is fixed.
-
-\subsection{Module\label{module}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Nested-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
-\medbreak
-\subsubsection{Values\label{values}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-X-val-x}\ocamlcodefragment{\ocamltag{keyword}{val} x : \hyperref[container-page-test+u+package+++ml-module-Nested-module-X-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of x.\end{ocamlindent}%
-\medbreak
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module X.\end{ocamlindent}%
-\medbreak
-\subsection{Module type\label{module-type}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-type-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Nested-module-type-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-type-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}%
-\medbreak
-\subsubsection{Values\label{values}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-type-Y-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[container-page-test+u+package+++ml-module-Nested-module-type-Y-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}%
-\medbreak
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module type Y.\end{ocamlindent}%
-\medbreak
-\subsection{Functor\label{functor}}%
-\label{container-page-test+u+package+++ml-module-Nested-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Nested-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ (\hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}} : \hyperref[container-page-test+u+package+++ml-module-Nested-module-type-Y]{\ocamlinlinecode{Y}}) (\hyperref[container-page-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is a functor F.\end{ocamlindent}%
-\medbreak
-\subsection{Class\label{class}}%
-\label{container-page-test+u+package+++ml-module-Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[container-page-test+u+package+++ml-module-Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[container-page-test+u+package+++ml-module-Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
-
-\input{test_package+ml/Nested.F.tex}
-\input{test_package+ml/Nested.z.tex}
-\input{test_package+ml/Nested.inherits.tex}
diff --git a/test/latex/expect/test_package+ml/Nested.z.tex b/test/latex/expect/test_package+ml/Nested.z.tex
deleted file mode 100644
index 9a6935c2cc..0000000000
--- a/test/latex/expect/test_package+ml/Nested.z.tex
+++ /dev/null
@@ -1,14 +0,0 @@
-\section{Class \ocamlinlinecode{Nested.\allowbreak{}z}}\label{container-page-test+u+package+++ml-module-Nested-class-z}%
-This is class z.
-
-Some additional comments.
-
-\label{container-page-test+u+package+++ml-module-Nested-class-z-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : int}\begin{ocamlindent}Some value.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Nested-class-z-val-y'}\ocamlcodefragment{\ocamltag{keyword}{val} \ocamltag{keyword}{mutable} \ocamltag{keyword}{virtual} y' : int}\\
-\subsection{Methods\label{methods}}%
-\label{container-page-test+u+package+++ml-module-Nested-class-z-method-z}\ocamlcodefragment{\ocamltag{keyword}{method} z : int}\begin{ocamlindent}Some method.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Nested-class-z-method-z'}\ocamlcodefragment{\ocamltag{keyword}{method} \ocamltag{keyword}{private} \ocamltag{keyword}{virtual} z' : int}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Recent.tex b/test/latex/expect/test_package+ml/Recent.tex
deleted file mode 100644
index 8803a7b57b..0000000000
--- a/test/latex/expect/test_package+ml/Recent.tex
+++ /dev/null
@@ -1,78 +0,0 @@
-\section{Module \ocamlinlinecode{Recent}}\label{container-page-test+u+package+++ml-module-Recent}%
-\label{container-page-test+u+package+++ml-module-Recent-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Recent-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Recent-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Recent-module-type-S1-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent-module-type-S1-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsubsection{Signature\label{signature}}%
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test+u+package+++ml-module-Recent-type-variant.A}%
-\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{container-page-test+u+package+++ml-module-Recent-type-variant.B}%
-\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{container-page-test+u+package+++ml-module-Recent-type-variant.C}%
-\begin{ocamlindent}foo\end{ocamlindent}%
-\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{container-page-test+u+package+++ml-module-Recent-type-variant.D}%
-\begin{ocamlindent}\emph{bar}\end{ocamlindent}%
-\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \{}\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Recent-type-variant.a}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{\}}\label{container-page-test+u+package+++ml-module-Recent-type-variant.E}%
-\begin{ocamlindent}\end{ocamlindent}%
-\end{ocamlindent}%
-\label{container-page-test+u+package+++ml-module-Recent-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[container-page-test+u+package+++ml-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test+u+package+++ml-module-Recent-type-gadt.A}%
-\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[container-page-test+u+package+++ml-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test+u+package+++ml-module-Recent-type-gadt.B}%
-\begin{ocamlindent}foo\end{ocamlindent}%
-\ocamlcodefragment{| \ocamltag{constructor}{C} : \{}\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Recent-type-gadt.a}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{\} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[container-page-test+u+package+++ml-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test+u+package+++ml-module-Recent-type-gadt.C}%
-\begin{ocamlindent}\end{ocamlindent}%
-\end{ocamlindent}%
-\label{container-page-test+u+package+++ml-module-Recent-type-polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\
-\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.A}& \\
-\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} int}\label{container-page-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.B}& \\
-\ocamlinlinecode{| }\ocamlinlinecode{`C}\label{container-page-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.C}& foo\\
-\ocamlinlinecode{| }\ocamlinlinecode{`D}\label{container-page-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.D}& bar\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{ ]}\\
-\label{container-page-test+u+package+++ml-module-Recent-type-empty+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}variant = |}\\
-\label{container-page-test+u+package+++ml-module-Recent-type-nonrec+u+}\ocamlcodefragment{\ocamltag{keyword}{type} \ocamltag{keyword}{nonrec} nonrec\_\allowbreak{} = int}\\
-\label{container-page-test+u+package+++ml-module-Recent-type-empty+u+conj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}conj = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of \& \ocamltag{type-var}{'a} \& int * float ] \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Recent-type-empty+u+conj]{\ocamlinlinecode{empty\_\allowbreak{}conj}}}\label{container-page-test+u+package+++ml-module-Recent-type-empty+u+conj.X}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Recent-type-conj}\ocamlcodefragment{\ocamltag{keyword}{type} conj = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of int \& [< `B of int \& float ] ] \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Recent-type-conj]{\ocamlinlinecode{conj}}}\label{container-page-test+u+package+++ml-module-Recent-type-conj.X}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Recent-val-empty+u+conj}\ocamlcodefragment{\ocamltag{keyword}{val} empty\_\allowbreak{}conj : [< `X of \& \ocamltag{type-var}{'a} \& int * float ]}\\
-\label{container-page-test+u+package+++ml-module-Recent-val-conj}\ocamlcodefragment{\ocamltag{keyword}{val} conj : [< `X of int \& [< `B of int \& float ] ]}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent-module-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent-module-Z-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} 'a t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent-module-X-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L := \hyperref[container-page-test+u+package+++ml-module-Recent-module-Z-module-Y]{\ocamlinlinecode{Z.\allowbreak{}Y}}}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int \hyperref[container-page-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u := int}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-X-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \hyperref[container-page-test+u+package+++ml-module-Recent-module-X-type-u]{\ocamlinlinecode{u}} \hyperref[container-page-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent-module-type-PolyS}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Recent-module-type-PolyS]{\ocamlinlinecode{PolyS}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent-module-type-PolyS-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = [ }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test+u+package+++ml-module-Recent-module-type-PolyS-type-t.A}\\
-\ocamlinlinecode{| }\ocamlinlinecode{`B}\label{container-page-test+u+package+++ml-module-Recent-module-type-PolyS-type-t.B}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{ ]}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Recent_impl.B.tex b/test/latex/expect/test_package+ml/Recent_impl.B.tex
deleted file mode 100644
index 57dabad832..0000000000
--- a/test/latex/expect/test_package+ml/Recent_impl.B.tex
+++ /dev/null
@@ -1,7 +0,0 @@
-\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl.\allowbreak{}B}}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-B}%
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-B-type-t.B}\\
-\end{ocamltabular}%
-\\
-
-
diff --git a/test/latex/expect/test_package+ml/Recent_impl.tex b/test/latex/expect/test_package+ml/Recent_impl.tex
deleted file mode 100644
index 64401c3a2e..0000000000
--- a/test/latex/expect/test_package+ml/Recent_impl.tex
+++ /dev/null
@@ -1,32 +0,0 @@
-\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl}}\label{container-page-test+u+package+++ml-module-Recent+u+impl}%
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A-type-t.A}\\
-\end{ocamltabular}%
-\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B-type-t.B}\\
-\end{ocamltabular}%
-\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}%
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\subsubsection{Signature\label{signature}}%
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-type-t]{\ocamlinlinecode{F(X).\allowbreak{}t}}}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Recent+u+impl-module-B'}\ocamlcodefragment{\ocamltag{keyword}{module} B' = \hyperref[container-page-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\
-
-\input{test_package+ml/Recent_impl.B.tex}
diff --git a/test/latex/expect/test_package+ml/Type.tex b/test/latex/expect/test_package+ml/Type.tex
deleted file mode 100644
index 142f29d9dc..0000000000
--- a/test/latex/expect/test_package+ml/Type.tex
+++ /dev/null
@@ -1,124 +0,0 @@
-\section{Module \ocamlinlinecode{Type}}\label{container-page-test+u+package+++ml-module-Type}%
-\label{container-page-test+u+package+++ml-module-Type-type-abstract}\ocamlcodefragment{\ocamltag{keyword}{type} abstract}\begin{ocamlindent}Some \emph{documentation}.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Type-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-private+u+}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{} = \ocamltag{keyword}{private} int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-constructor}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constructor = \ocamltag{type-var}{'a}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-arrow}\ocamlcodefragment{\ocamltag{keyword}{type} arrow = int \ocamltag{arrow}{$\rightarrow$} int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-higher+u+order}\ocamlcodefragment{\ocamltag{keyword}{type} higher\_\allowbreak{}order = (int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-labeled}\ocamlcodefragment{\ocamltag{keyword}{type} labeled = l:int \ocamltag{arrow}{$\rightarrow$} int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-optional}\ocamlcodefragment{\ocamltag{keyword}{type} optional = ?l:int \ocamltag{arrow}{$\rightarrow$} int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-labeled+u+higher+u+order}\ocamlcodefragment{\ocamltag{keyword}{type} labeled\_\allowbreak{}higher\_\allowbreak{}order = (l:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (?l:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-pair}\ocamlcodefragment{\ocamltag{keyword}{type} pair = int * int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-parens+u+dropped}\ocamlcodefragment{\ocamltag{keyword}{type} parens\_\allowbreak{}dropped = int * int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-triple}\ocamlcodefragment{\ocamltag{keyword}{type} triple = int * int * int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-nested+u+pair}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}pair = (int * int) * int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-instance}\ocamlcodefragment{\ocamltag{keyword}{type} instance = int \hyperref[container-page-test+u+package+++ml-module-Type-type-constructor]{\ocamlinlinecode{constructor}}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-long}\ocamlcodefragment{\ocamltag{keyword}{type} long = \hyperref[container-page-test+u+package+++ml-module-Type-type-labeled+u+higher+u+order]{\ocamlinlinecode{labeled\_\allowbreak{}higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} [ `Bar | `Baz of \hyperref[container-page-test+u+package+++ml-module-Type-type-triple]{\ocamlinlinecode{triple}} ] \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Type-type-pair]{\ocamlinlinecode{pair}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Type-type-labeled]{\ocamlinlinecode{labeled}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Type-type-higher+u+order]{\ocamlinlinecode{higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} (string \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (int,\allowbreak{} float,\allowbreak{} char,\allowbreak{} string,\allowbreak{} char,\allowbreak{} unit) \hyperref[xref-unresolved]{\ocamlinlinecode{CamlinternalFormatBasics}}.\allowbreak{}fmtty \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Type-type-nested+u+pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Type-type-arrow]{\ocamlinlinecode{arrow}} \ocamltag{arrow}{$\rightarrow$} string \ocamltag{arrow}{$\rightarrow$} \hyperref[container-page-test+u+package+++ml-module-Type-type-nested+u+pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} array}\\
-\label{container-page-test+u+package+++ml-module-Type-type-variant+u+e}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}e = \{}\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-variant+u+e.a}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{\}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\
-\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test+u+package+++ml-module-Type-type-variant.A}& \\
-\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{container-page-test+u+package+++ml-module-Type-type-variant.B}& \\
-\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{container-page-test+u+package+++ml-module-Type-type-variant.C}& foo\\
-\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{container-page-test+u+package+++ml-module-Type-type-variant.D}& \emph{bar}\\
-\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \hyperref[container-page-test+u+package+++ml-module-Type-type-variant+u+e]{\ocamlinlinecode{variant\_\allowbreak{}e}}}\label{container-page-test+u+package+++ml-module-Type-type-variant.E}& \\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-type-variant+u+c}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}c = \{}\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-variant+u+c.a}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{\}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[container-page-test+u+package+++ml-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test+u+package+++ml-module-Type-type-gadt.A}\\
-\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[container-page-test+u+package+++ml-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test+u+package+++ml-module-Type-type-gadt.B}\\
-\ocamlcodefragment{| \ocamltag{constructor}{C} : \hyperref[container-page-test+u+package+++ml-module-Type-type-variant+u+c]{\ocamlinlinecode{variant\_\allowbreak{}c}} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[container-page-test+u+package+++ml-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{container-page-test+u+package+++ml-module-Type-type-gadt.C}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-type-degenerate+u+gadt}\ocamlcodefragment{\ocamltag{keyword}{type} degenerate\_\allowbreak{}gadt = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : \hyperref[container-page-test+u+package+++ml-module-Type-type-degenerate+u+gadt]{\ocamlinlinecode{degenerate\_\allowbreak{}gadt}}}\label{container-page-test+u+package+++ml-module-Type-type-degenerate+u+gadt.A}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-type-private+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}variant = \ocamltag{keyword}{private} }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{container-page-test+u+package+++ml-module-Type-type-private+u+variant.A}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\
-\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-record.a}& \\
-\ocamlinlinecode{\ocamltag{keyword}{mutable} b : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-record.b}& \\
-\ocamlinlinecode{c : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-record.c}& foo\\
-\ocamlinlinecode{d : int;\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-record.d}& \emph{bar}\\
-\ocamlinlinecode{e : a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{}}\label{container-page-test+u+package+++ml-module-Type-type-record.e}& \\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{\}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant.A}\\
-\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} int}\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant.B}\\
-\ocamlinlinecode{| }\ocamlinlinecode{`C \ocamltag{keyword}{of} int * unit}\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant.C}\\
-\ocamlinlinecode{| }\ocamlinlinecode{`D}\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant.D}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{ ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant\_\allowbreak{}extension = [ }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension.polymorphic+u+variant}\\
-\ocamlinlinecode{| }\ocamlinlinecode{`E}\label{container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension.E}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{ ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-nested+u+polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}polymorphic\_\allowbreak{}variant = [ }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A \ocamltag{keyword}{of} [ `B | `C ]}\label{container-page-test+u+package+++ml-module-Type-type-nested+u+polymorphic+u+variant.A}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{ ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-private+u+extenion#row}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}extenion\#row}\\
-\label{container-page-test+u+package+++ml-module-Type-type-private+u+extenion}\ocamlcodefragment{\ocamltag{keyword}{and} private\_\allowbreak{}extenion = \ocamltag{keyword}{private} [> }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{container-page-test+u+package+++ml-module-Type-type-private+u+extenion.polymorphic+u+variant}\\
-\end{ocamltabular}%
-\\
-\ocamlcodefragment{ ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-object+u+}\ocamlcodefragment{\ocamltag{keyword}{type} object\_\allowbreak{} = < a : int;\allowbreak{} b : int;\allowbreak{} c : int;\allowbreak{} >}\\
-\label{container-page-test+u+package+++ml-module-Type-module-type-X}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Type-module-type-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{container-page-test+u+package+++ml-module-Type-module-type-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\
-\label{container-page-test+u+package+++ml-module-Type-module-type-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\
-\end{ocamlindent}%
-\ocamlcodefragment{\ocamltag{keyword}{end}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-module+u+}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{} = (\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Type-module-type-X]{\ocamlinlinecode{X}})}\\
-\label{container-page-test+u+package+++ml-module-Type-type-module+u+substitution}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{}substitution = (\ocamltag{keyword}{module} \hyperref[container-page-test+u+package+++ml-module-Type-module-type-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Type-module-type-X-type-t]{\ocamlinlinecode{t}} = int \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Type-module-type-X-type-u]{\ocamlinlinecode{u}} = unit)}\\
-\label{container-page-test+u+package+++ml-module-Type-type-covariant}\ocamlcodefragment{\ocamltag{keyword}{type} +'a covariant}\\
-\label{container-page-test+u+package+++ml-module-Type-type-contravariant}\ocamlcodefragment{\ocamltag{keyword}{type} -'a contravariant}\\
-\label{container-page-test+u+package+++ml-module-Type-type-bivariant}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} bivariant = int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-binary}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) binary}\\
-\label{container-page-test+u+package+++ml-module-Type-type-using+u+binary}\ocamlcodefragment{\ocamltag{keyword}{type} using\_\allowbreak{}binary = (int,\allowbreak{} int) \hyperref[container-page-test+u+package+++ml-module-Type-type-binary]{\ocamlinlinecode{binary}}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-name}\ocamlcodefragment{\ocamltag{keyword}{type} 'custom name}\\
-\label{container-page-test+u+package+++ml-module-Type-type-constrained}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constrained = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int}\\
-\label{container-page-test+u+package+++ml-module-Type-type-exact+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [ `A | `B of int ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-lower+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `A | `B of int ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-any+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-upper+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a upper\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< `A | `B of int ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-named+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a named\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< \hyperref[container-page-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}} ]}\\
-\label{container-page-test+u+package+++ml-module-Type-type-exact+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int;\allowbreak{} b : int;\allowbreak{} >}\\
-\label{container-page-test+u+package+++ml-module-Type-type-lower+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int;\allowbreak{} b : int;\allowbreak{} .\allowbreak{}.\allowbreak{} >}\\
-\label{container-page-test+u+package+++ml-module-Type-type-poly+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{} >}\\
-\label{container-page-test+u+package+++ml-module-Type-type-double+u+constrained}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) double\_\allowbreak{}constrained = \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int \ocamltag{keyword}{constraint} \ocamltag{type-var}{'b} = unit}\\
-\label{container-page-test+u+package+++ml-module-Type-type-as+u+}\ocamlcodefragment{\ocamltag{keyword}{type} as\_\allowbreak{} = int \ocamltag{keyword}{as} 'a * \ocamltag{type-var}{'a}}\\
-\label{container-page-test+u+package+++ml-module-Type-type-extensible}\ocamlcodefragment{\ocamltag{keyword}{type} extensible = .\allowbreak{}.\allowbreak{}}\\
-\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[container-page-test+u+package+++ml-module-Type-type-extensible]{\ocamlinlinecode{extensible}} += }\\
-\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Extension}}\label{container-page-test+u+package+++ml-module-Type-extension-Extension}& Documentation for \hyperref[container-page-test+u+package+++ml-module-Type-extension-Extension]{\ocamlinlinecode{\ocamlinlinecode{Extension}}[p\pageref*{container-page-test+u+package+++ml-module-Type-extension-Extension}]}.\\
-\ocamlcodefragment{| \ocamltag{extension}{Another\_\allowbreak{}extension}}\label{container-page-test+u+package+++ml-module-Type-extension-Another+u+extension}& Documentation for \hyperref[container-page-test+u+package+++ml-module-Type-extension-Another+u+extension]{\ocamlinlinecode{\ocamlinlinecode{Another\_\allowbreak{}extension}}[p\pageref*{container-page-test+u+package+++ml-module-Type-extension-Another+u+extension}]}.\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{type} mutually = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[container-page-test+u+package+++ml-module-Type-type-recursive]{\ocamlinlinecode{recursive}}}\label{container-page-test+u+package+++ml-module-Type-type-mutually.A}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{and} recursive = }\\
-\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} \hyperref[container-page-test+u+package+++ml-module-Type-type-mutually]{\ocamlinlinecode{mutually}}}\label{container-page-test+u+package+++ml-module-Type-type-recursive.B}\\
-\end{ocamltabular}%
-\\
-\label{container-page-test+u+package+++ml-module-Type-exception-Foo}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Foo} \ocamltag{keyword}{of} int * int}\\
-
-
diff --git a/test/latex/expect/test_package+ml/Val.tex b/test/latex/expect/test_package+ml/Val.tex
deleted file mode 100644
index 220f4fad27..0000000000
--- a/test/latex/expect/test_package+ml/Val.tex
+++ /dev/null
@@ -1,8 +0,0 @@
-\section{Module \ocamlinlinecode{Val}}\label{container-page-test+u+package+++ml-module-Val}%
-\label{container-page-test+u+package+++ml-module-Val-val-documented}\ocamlcodefragment{\ocamltag{keyword}{val} documented : unit}\begin{ocamlindent}Foo.\end{ocamlindent}%
-\medbreak
-\label{container-page-test+u+package+++ml-module-Val-val-undocumented}\ocamlcodefragment{\ocamltag{keyword}{val} undocumented : unit}\\
-\label{container-page-test+u+package+++ml-module-Val-val-documented+u+above}\ocamlcodefragment{\ocamltag{keyword}{val} documented\_\allowbreak{}above : unit}\begin{ocamlindent}Bar.\end{ocamlindent}%
-\medbreak
-
-
diff --git a/test/latex/expect/visualizer.tex b/test/latex/expect/visualizer.tex
deleted file mode 100644
index 35b487a614..0000000000
--- a/test/latex/expect/visualizer.tex
+++ /dev/null
@@ -1,90 +0,0 @@
-% Helper files for transforming the test files into a pdf
-% compile with
-% TEXINPUTS=${TEXINPUTS}:test_package+ml/ xelatex visualizer.tex
-%
-\documentclass{book}
-
-\usepackage{fontspec}
-\usepackage{xunicode}
-
-\usepackage{changepage}
-\usepackage{longtable}
-\usepackage{listings}
-\usepackage[strings]{underscore}
-
-\usepackage[colorlinks=true]{hyperref}
-\usepackage{color}
-\usepackage{lmodern}
-\usepackage[T1]{fontenc}
-
-\newcommand{\ocamlcodefragment}[1]{{\ttfamily\setlength{\parindent}{0cm}%
-\raggedright#1}}
-\newcommand{\ocamlinlinecode}[1]{{\ttfamily#1}}
-\newcommand{\bold}[1]{{\bfseries#1}}
-\newenvironment{ocamlexception}{\bfseries}{}
-\newenvironment{ocamlextension}{\bfseries}{}
-
-\newenvironment{ocamlkeyword}{\bfseries}{}
-
-\newenvironment{ocamlconstructor}{\bfseries}{}
-\newenvironment{ocamltype-var}{\itshape\ttfamily}{}
-
-\newcommand{\ocamlhighlight}{\bfseries\uline}
-\newcommand{\ocamlerror}{\bfseries}
-\newcommand{\ocamlwarning}{\bfseries}
-
-\newcommand{\ocamltag}[2]{\begin{ocaml#1}#2\end{ocaml#1}}
-
-\definecolor{lightgray}{gray}{0.97}
-\definecolor{gray}{gray}{0.5}
-\newcommand{\ocamlcomment}{\color{gray}\normalfont\small}
-\newcommand{\ocamlstring}{\color{gray}\bfseries}
-\newenvironment{ocamlindent}{\begin{adjustwidth}{2em}{0pt}}{\end{adjustwidth}}
-\newenvironment{ocamltabular}[1]{\begin{tabular}{#1}}%
-{\end{tabular}}
-
-\lstnewenvironment{ocamlcodeblock}{
- \lstset{
- backgroundcolor = \color{lightgray},
- basicstyle=\ttfamily,
- showstringspaces=false,
- language=caml,
- escapeinside={$}{$},
- columns=fullflexible,
- stringstyle=\ocamlstring,
- commentstyle=\ocamlcomment,
- keepspaces=true,
- keywordstyle=\ocamlkeyword,
- moredelim=[is][\ocamlhighlight]{<<}{>>},
- moredelim=[s][\ocamlstring]{\{|}{|\}},
- moredelim=[s][\ocamlstring]{\{delimiter|}{|delimiter\}},
- keywords={[2]{val,initializer,nonrec}}, keywordstyle={[2]\ocamlkeyword},
- belowskip=0\baselineskip,
- upquote=true,
- literate={'"'}{\textquotesingle "\textquotesingle}3
- {'\\"'}{\textquotesingle \textbackslash"\textquotesingle}4,
- }
- }{}
-
- \newcommand{\inputchapter}[1]{\chapter{#1}
- \input{#1}}
-
- \begin{document}
-\inputchapter{Recent}
-\inputchapter{Recent_impl}
-\inputchapter{Val}
-\inputchapter{Markup}
-\inputchapter{Section}
-\inputchapter{Module}
-\inputchapter{Include}
-\inputchapter{Include2}
-\inputchapter{Mld}
-\inputchapter{Nested}
-\inputchapter{External}
-\inputchapter{Functor}
-\inputchapter{Class}
-\inputchapter{Stop}
-\inputchapter{Bugs}
-\inputchapter{Bugs_pre_410}
-\inputchapter{Alias}
-\end{document}
diff --git a/test/latex/test.ml b/test/latex/test.ml
deleted file mode 100644
index e0c4b137bc..0000000000
--- a/test/latex/test.ml
+++ /dev/null
@@ -1,238 +0,0 @@
-open Printf
-
-(* Utils *)
-
-let ( // ) = Filename.concat
-
-let command label =
- Printf.ksprintf (fun s ->
- let exit_code = Sys.command s in
- if exit_code <> 0 then
- Alcotest.failf "'%s' exited with %i" label exit_code)
-
-(* Filename.extension is only available on 4.04. *)
-module Filename = struct
- include Filename
-
- let extension filename =
- let dot_index = String.rindex filename '.' in
- String.sub filename dot_index (String.length filename - dot_index)
-end
-
-(* Testing environment *)
-
-module Env = struct
- let package = "test_package"
-
- let odoc = "../../src/odoc/bin/main.exe"
-
- let path ?(from_root = false) = function
- | `scratch when from_root -> "_build/default/test/latex/_scratch"
- | `scratch -> "_scratch"
- | `expect when from_root -> "test/latex/expect"
- | `expect -> "expect"
- | `cases when from_root -> "test/cases"
- | `cases -> "../cases"
-
- let init () = Unix.mkdir (path `scratch) 0o755
-end
-
-(* Test case type and helpers *)
-
-(* A test case is a description of an input source file with a specific set of
- options to be tested. Each test case results in a unique generated output to
- be compared with an actually produced one.
-
- All paths defined in this module are relative to the build directory. *)
-module Case = struct
- type t = {
- name : string;
- kind : [ `mli | `mld | `ml ];
- syntax : [ `ml | `re ];
- outputs : string list;
- }
-
- let make ?(syntax = `ml) (input, outputs) =
- let name = Filename.chop_extension input in
- let kind =
- match Filename.extension input with
- | ".mli" -> `mli
- | ".mld" -> `mld
- | ".ml" -> `ml
- | _ ->
- invalid_arg (sprintf "Expected mli, mld, or ml files, got %s" input)
- in
- { name; kind; syntax; outputs }
-
- let name case = case.name
-
- let kind case = case.kind
-
- let string_of_syntax = function `re -> "re" | `ml -> "ml"
-
- (* The package name is enriched with test case options. *)
- let package case =
- let opts = [ string_of_syntax case.syntax ] in
- let opts = String.concat "," (List.sort compare opts) in
- Env.package ^ "+" ^ opts
-
- let cmi_file case = Env.path `scratch // (case.name ^ ".cmi")
-
- let cmti_file case = Env.path `scratch // (case.name ^ ".cmti")
-
- let cmo_file case = Env.path `scratch // (case.name ^ ".cmo")
-
- let cmt_file case = Env.path `scratch // (case.name ^ ".cmt")
-
- let odoc_file case =
- match case.kind with
- | `mli | `ml -> Env.path `scratch // (case.name ^ ".odoc")
- | `mld -> Env.path `scratch // ("page-" ^ case.name ^ ".odoc")
-
- let source_file case =
- match case.kind with
- | `mli -> (Env.path `cases // case.name) ^ ".mli"
- | `mld -> (Env.path `cases // case.name) ^ ".mld"
- | `ml -> (Env.path `cases // case.name) ^ ".ml"
-
- let outputs case = List.map (fun o -> package case // o) case.outputs
-end
-
-let generate_latex case =
- match Case.kind case with
- | `mli ->
- command "ocamlfind c" "ocamlfind c -bin-annot -o %s -c %s"
- (Case.cmi_file case) (Case.source_file case);
-
- command "odoc compile" "%s compile --package=%s %s" Env.odoc
- (Case.package case) (Case.cmti_file case);
-
- command "odoc latex" "%s latex --syntax=%s --output-dir=%s %s" Env.odoc
- (Case.string_of_syntax case.syntax)
- (Env.path `scratch)
- (Case.odoc_file case)
- | `mld ->
- command "odoc compile" "%s compile --package=%s -o %s %s" Env.odoc
- (Case.package case) (Case.odoc_file case) (Case.source_file case);
-
- command "odoc latex" "%s latex --output-dir=%s %s" Env.odoc
- (Env.path `scratch)
- (Case.odoc_file case)
- | `ml ->
- command "ocamlfind c" "ocamlfind c -bin-annot -o %s -c %s"
- (Case.cmo_file case) (Case.source_file case);
-
- command "odoc compile" "%s compile --package=%s %s" Env.odoc
- (Case.package case) (Case.cmt_file case);
-
- command "odoc latex" "%s latex --syntax=%s --output-dir=%s %s" Env.odoc
- (Case.string_of_syntax case.syntax)
- (Env.path `scratch)
- (Case.odoc_file case)
-
-let diff =
- (* Alcotest will run all tests. We need to know when something fails for the
- first time to stop diffing and generating promotion files. *)
- let already_failed = ref false in
- fun output ->
- let actual_file = Env.path `scratch // output in
- let expected_file = Env.path `expect // output in
- let cmd = sprintf "diff -N -u -b %s %s" expected_file actual_file in
- match Sys.command cmd with
- | 0 -> ()
- | 1 when !already_failed ->
- (* Don't run diff for other failing tests as only one at time is shown. *)
- Alcotest.fail "generated latex files should match expected"
- | 1 ->
- (* If the diff command exits with 1, the two MAN files are different.
- diff has already written its output to STDOUT.
-
- Also provide the command for overwriting the expected output with the
- actual output, in case it is the actual output that is correct.
- The paths are defined relative to the project's root. *)
- let root_actual_file = Env.path `scratch ~from_root:true // output in
- let root_expected_file = Env.path `expect ~from_root:true // output in
- let write_file filename data =
- let oc = open_out filename in
- output_string oc data;
- close_out oc
- in
- write_file Env.(path `scratch // "actual") root_actual_file;
- write_file Env.(path `scratch // "expected") root_expected_file;
-
- prerr_endline "\nTo promote the actual output to expected, run:";
- Printf.eprintf "cp `cat %s` `cat %s` && make test\n\n"
- Env.(path ~from_root:true `scratch // "actual")
- Env.(path ~from_root:true `scratch // "expected");
-
- already_failed := true;
- Alcotest.fail "generated latex files should match expected"
- | exit_code -> Alcotest.failf "'diff' exited with %i" exit_code
-
-let make_test_case ?syntax case =
- let case = Case.make ?syntax case in
- let run () =
- (* Compile the source file and generate latex files. *)
- generate_latex case;
-
- List.iter diff (Case.outputs case)
- in
- (Case.name case, `Slow, run)
-
-let source_files_all =
- [
- ("val.mli", [ "Val.tex" ]);
- ("markup.mli", [ "Markup.tex" ]);
- ("section.mli", [ "Section.tex" ]);
- ("module.mli", [ "Module.tex" ]);
- ("interlude.mli", [ "Interlude.tex" ]);
- ("include.mli", [ "Include.tex" ]);
- ("include2.ml", [ "Include2.tex" ]);
- ("include_sections.mli", [ "Include_sections.tex" ]);
- ("mld.mld", [ "mld.tex" ]);
- ( "nested.mli",
- [ "Nested.tex"; "Nested.F.tex"; "Nested.z.tex"; "Nested.inherits.tex" ] );
- ("type.mli", [ "Type.tex" ]);
- ("external.mli", [ "External.tex" ]);
- ( "functor.mli",
- [
- "Functor.tex";
- "Functor.F1.tex";
- "Functor.F2.tex";
- "Functor.F3.tex";
- "Functor.F4.tex";
- ] );
- ("class.mli", [ "Class.tex" ]);
- ("stop.mli", [ "Stop.tex" ]);
- ("bugs.ml", [ "Bugs.tex" ]);
- ("alias.ml", [ "Alias.tex"; "Alias.X.tex" ]);
- ]
-
-let source_files_post408 =
- [
- ("recent.mli", [ "Recent.tex" ]);
- ("recent_impl.ml", [ "Recent_impl.tex"; "Recent_impl.B.tex" ]);
- ]
-
-let source_files_pre410 = [ ("bugs_pre_410.ml", [ "Bugs_pre_410.tex" ]) ]
-
-let source_files =
- let cur =
- Astring.String.cuts ~sep:"." Sys.ocaml_version
- |> List.map (fun i -> try Some (int_of_string i) with _ -> None)
- in
- match cur with
- | Some major :: Some minor :: _ ->
- List.concat
- [
- (if major = 4 && minor < 10 then source_files_pre410 else []);
- (if major = 4 && minor > 8 then source_files_post408 else []);
- source_files_all;
- ]
- | _ -> source_files_all
-
-let () =
- Env.init ();
-
- Alcotest.run "latex"
- [ ("latex_ml", List.map (make_test_case ~syntax:`ml) source_files) ]
diff --git a/test/man/dune b/test/man/dune
deleted file mode 100644
index 0ddf0a06f1..0000000000
--- a/test/man/dune
+++ /dev/null
@@ -1,13 +0,0 @@
-(executable
- (name test)
- (libraries alcotest))
-
-(rule
- (alias runtest)
- (action
- (run %{exe:test.exe}))
- (deps
- test.exe
- %{workspace_root}/src/odoc/bin/main.exe
- (source_tree ../cases)
- (source_tree expect)))
diff --git a/test/man/expect/test_package+ml/mld.nroff b/test/man/expect/test_package+ml/mld.nroff
deleted file mode 100644
index b0b576b69d..0000000000
--- a/test/man/expect/test_package+ml/mld.nroff
+++ /dev/null
@@ -1,63 +0,0 @@
-
-.TH mld 3 "" "Odoc" "OCaml Library"
-.SH Name
-test_package+ml\.mld
-.SH Synopsis
-.sp
-.in 2
-\fBMld Page\fR
-.in
-.sp
-.fi
-This is an \.mld file\. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do\.
-.sp
-It will have a TOC generated from section headings\.
-.nf
-.SH Documentation
-.sp
-.nf
-.sp
-.in 3
-\fB1 Section\fR
-.in
-.sp
-.fi
-This is a section\.
-.sp
-Another paragraph in section\.
-.nf
-.sp
-.in 3
-\fB2 Another section\fR
-.in
-.sp
-.fi
-This is another section\.
-.sp
-Another paragraph in section 2\.
-.nf
-.sp
-.in 4
-\fB2\.1 Subsection\fR
-.in
-.sp
-.fi
-This is a subsection\.
-.sp
-Another paragraph in subsection\.
-.sp
-Yet another paragraph in subsection\.
-.nf
-.sp
-.in 4
-\fB2\.2 Another Subsection\fR
-.in
-.sp
-.fi
-This is another subsection\.
-.sp
-Another paragraph in subsection 2\.
-.sp
-Yet another paragraph in subsection 2\.
-.nf
-
diff --git a/test/man/test.ml b/test/man/test.ml
deleted file mode 100644
index e67a876dd5..0000000000
--- a/test/man/test.ml
+++ /dev/null
@@ -1,244 +0,0 @@
-open Printf
-
-(* Utils *)
-
-let ( // ) = Filename.concat
-
-let command label =
- Printf.ksprintf (fun s ->
- let exit_code = Sys.command s in
- if exit_code <> 0 then
- Alcotest.failf "'%s' exited with %i" label exit_code)
-
-(* Filename.extension is only available on 4.04. *)
-module Filename = struct
- include Filename
-
- let extension filename =
- let dot_index = String.rindex filename '.' in
- String.sub filename dot_index (String.length filename - dot_index)
-end
-
-(* Testing environment *)
-
-module Env = struct
- let package = "test_package"
-
- let odoc = "../../src/odoc/bin/main.exe"
-
- let path ?(from_root = false) = function
- | `scratch when from_root -> "_build/default/test/man/_scratch"
- | `scratch -> "_scratch"
- | `expect when from_root -> "test/man/expect"
- | `expect -> "expect"
- | `cases when from_root -> "test/cases"
- | `cases -> "../cases"
-
- let init () = Unix.mkdir (path `scratch) 0o755
-end
-
-(* Test case type and helpers *)
-
-(* A test case is a description of an input source file with a specific set of
- options to be tested. Each test case results in a unique generated output to
- be compared with an actually produced one.
-
- All paths defined in this module are relative to the build directory. *)
-module Case = struct
- type t = {
- name : string;
- kind : [ `mli | `mld | `ml ];
- syntax : [ `ml | `re ];
- outputs : string list;
- }
-
- let make ?(syntax = `ml) (input, outputs) =
- let name = Filename.chop_extension input in
- let kind =
- match Filename.extension input with
- | ".mli" -> `mli
- | ".mld" -> `mld
- | ".ml" -> `ml
- | _ ->
- invalid_arg (sprintf "Expected mli, mld, or ml files, got %s" input)
- in
- { name; kind; syntax; outputs }
-
- let name case = case.name
-
- let kind case = case.kind
-
- let string_of_syntax = function `re -> "re" | `ml -> "ml"
-
- (* The package name is enriched with test case options. *)
- let package case =
- let opts = [ string_of_syntax case.syntax ] in
- let opts = String.concat "," (List.sort compare opts) in
- Env.package ^ "+" ^ opts
-
- let cmi_file case = Env.path `scratch // (case.name ^ ".cmi")
-
- let cmti_file case = Env.path `scratch // (case.name ^ ".cmti")
-
- let cmo_file case = Env.path `scratch // (case.name ^ ".cmo")
-
- let cmt_file case = Env.path `scratch // (case.name ^ ".cmt")
-
- let odoc_file case =
- match case.kind with
- | `mli | `ml -> Env.path `scratch // (case.name ^ ".odoc")
- | `mld -> Env.path `scratch // ("page-" ^ case.name ^ ".odoc")
-
- let source_file case =
- match case.kind with
- | `mli -> (Env.path `cases // case.name) ^ ".mli"
- | `mld -> (Env.path `cases // case.name) ^ ".mld"
- | `ml -> (Env.path `cases // case.name) ^ ".ml"
-
- let outputs case = List.map (fun o -> package case // o) case.outputs
-end
-
-let generate_man case =
- match Case.kind case with
- | `mli ->
- command "ocamlfind c" "ocamlfind c -bin-annot -o %s -c %s"
- (Case.cmi_file case) (Case.source_file case);
-
- command "odoc compile" "%s compile --package=%s %s" Env.odoc
- (Case.package case) (Case.cmti_file case);
-
- command "odoc man" "%s man --syntax=%s --output-dir=%s %s" Env.odoc
- (Case.string_of_syntax case.syntax)
- (Env.path `scratch)
- (Case.odoc_file case)
- | `mld ->
- command "odoc compile" "%s compile --package=%s -o %s %s" Env.odoc
- (Case.package case) (Case.odoc_file case) (Case.source_file case);
-
- command "odoc man" "%s man --output-dir=%s %s" Env.odoc
- (Env.path `scratch)
- (Case.odoc_file case)
- | `ml ->
- command "ocamlfind c" "ocamlfind c -bin-annot -o %s -c %s"
- (Case.cmo_file case) (Case.source_file case);
-
- command "odoc compile" "%s compile --package=%s %s" Env.odoc
- (Case.package case) (Case.cmt_file case);
-
- command "odoc man" "%s man --syntax=%s --output-dir=%s %s" Env.odoc
- (Case.string_of_syntax case.syntax)
- (Env.path `scratch)
- (Case.odoc_file case)
-
-let diff =
- (* Alcotest will run all tests. We need to know when something fails for the
- first time to stop diffing and generating promotion files. *)
- let already_failed = ref false in
- fun output ->
- let actual_file = Env.path `scratch // output in
- let expected_file = Env.path `expect // output in
- let cmd = sprintf "diff -N -u -b %s %s" expected_file actual_file in
- match Sys.command cmd with
- | 0 -> ()
- | 1 when !already_failed ->
- (* Don't run diff for other failing tests as only one at time is shown. *)
- Alcotest.fail "generated MAN should match expected"
- | 1 ->
- (* If the diff command exits with 1, the two MAN files are different.
- diff has already written its output to STDOUT.
-
- Also provide the command for overwriting the expected output with the
- actual output, in case it is the actual output that is correct.
- The paths are defined relative to the project's root. *)
- let root_actual_file = Env.path `scratch ~from_root:true // output in
- let root_expected_file = Env.path `expect ~from_root:true // output in
- let write_file filename data =
- let oc = open_out filename in
- output_string oc data;
- close_out oc
- in
- write_file Env.(path `scratch // "actual") root_actual_file;
- write_file Env.(path `scratch // "expected") root_expected_file;
-
- prerr_endline "\nTo promote the actual output to expected, run:";
- Printf.eprintf "cp `cat %s` `cat %s` && make test\n\n"
- Env.(path ~from_root:true `scratch // "actual")
- Env.(path ~from_root:true `scratch // "expected");
-
- already_failed := true;
- Alcotest.fail "generated MAN should match expected"
- | exit_code -> Alcotest.failf "'diff' exited with %i" exit_code
-
-let make_test_case ?syntax case =
- let case = Case.make ?syntax case in
- let run () =
- (* Compile the source file and generate MAN. *)
- generate_man case;
-
- List.iter diff (Case.outputs case)
- in
- (Case.name case, `Slow, run)
-
-let source_files_all =
- [
- ("val.mli", [ "Val.3o" ]);
- ("markup.mli", [ "Markup.3o" ]);
- ("section.mli", [ "Section.3o" ]);
- ("module.mli", [ "Module.3o" ]);
- ("interlude.mli", [ "Interlude.3o" ]);
- ("include.mli", [ "Include.3o" ]);
- ("include2.ml", [ "Include2.3o" ]);
- ("include_sections.mli", [ "Include_sections.3o" ]);
- ("mld.mld", [ "mld.3o" ]);
- ( "nested.mli",
- [
- "Nested.3o";
- "Nested.F.3o";
- "Nested.X.3o";
- "Nested.z.3o";
- "Nested.inherits.3o";
- ] );
- ("type.mli", [ "Type.3o" ]);
- ("external.mli", [ "External.3o" ]);
- ( "functor.mli",
- [
- "Functor.3o";
- "Functor.F1.3o";
- "Functor.F2.3o";
- "Functor.F3.3o";
- "Functor.F4.3o";
- ] );
- ("class.mli", [ "Class.3o" ]);
- ("stop.mli", [ "Stop.3o" ]);
- ("bugs.ml", [ "Bugs.3o" ]);
- ("alias.ml", [ "Alias.3o"; "Alias.X.3o" ]);
- ]
-
-let source_files_post408 =
- [
- ("recent.mli", [ "Recent.3o"; "Recent.X.3o" ]);
- ("recent_impl.ml", [ "Recent_impl.3o" ]);
- ]
-
-let source_files_pre410 = [ ("bugs_pre_410.ml", [ "Bugs_pre_410.3o" ]) ]
-
-let source_files =
- let cur =
- Astring.String.cuts ~sep:"." Sys.ocaml_version
- |> List.map (fun i -> try Some (int_of_string i) with _ -> None)
- in
- match cur with
- | Some major :: Some minor :: _ ->
- List.concat
- [
- (if major = 4 && minor < 10 then source_files_pre410 else []);
- (if major = 4 && minor > 8 then source_files_post408 else []);
- source_files_all;
- ]
- | _ -> source_files_all
-
-let () =
- Env.init ();
-
- Alcotest.run "man"
- [ ("man_ml", List.map (make_test_case ~syntax:`ml) source_files) ]