diff --git a/src/html/generator.ml b/src/html/generator.ml index e099813c12..d9dff60a73 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -33,11 +33,12 @@ let mk_anchor_link id = let mk_anchor anchor = match anchor with - | None -> ([], []) + | None -> ([], [], []) | Some { Odoc_document.Url.Anchor.anchor; _ } -> let link = mk_anchor_link anchor in - let attrib = [ Html.a_id anchor; Html.a_class [ "anchored" ] ] in - (attrib, link) + let extra_attr = [ Html.a_id anchor ] in + let extra_class = [ "anchored" ] in + (extra_attr, extra_class, link) let class_ (l : Class.t) = if l = [] then [] else [ Html.a_class l ] @@ -204,7 +205,7 @@ let div : ([< Html_types.div_attrib ], [< item ], [> Html_types.div ]) Html.star = Html.Unsafe.node "div" -let spec_class = function [] -> [] | attr -> class_ ("spec" :: attr) +let spec_class attr = class_ ("spec" :: attr) let spec_doc_div ~resolve = function | [] -> [] @@ -250,28 +251,22 @@ let rec documentedSrc ~resolve (t : DocumentedSrc.t) : item Html.elt list = | [] -> [] | doc -> let opening, closing = markers in + let delim s = + [ Html.span ~a:(class_ [ "comment-delim" ]) [ Html.txt s ] ] + in [ - Html.td + Html.div ~a:(class_ [ "def-doc" ]) - (Html.span - ~a:(class_ [ "comment-delim" ]) - [ Html.txt opening ] - :: block ~resolve doc - @ [ - Html.span - ~a:(class_ [ "comment-delim" ]) - [ Html.txt closing ]; - ]); + (delim opening @ block ~resolve doc @ delim closing); ] in - let a, link = mk_anchor anchor in - let content = - let c = link @ content in - Html.td ~a:(class_ attrs) (c :> any Html.elt list) - in - Html.tr ~a (content :: doc) + let extra_attr, extra_class, link = mk_anchor anchor in + let content = (content :> any Html.elt list) in + Html.li + ~a:(extra_attr @ class_ (attrs @ extra_class)) + (link @ content @ doc) in - Html.table (List.map one l) :: to_html rest + Html.ol (List.map one l) :: to_html rest in to_html t @@ -307,8 +302,8 @@ and items ~resolve l : item Html.elt list = let details ~open' = let open' = if open' then [ Html.a_open () ] else [] in let summary = - let anchor_attrib, anchor_link = mk_anchor anchor in - let a = spec_class attr @ anchor_attrib in + let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let a = spec_class (attr @ extra_class) @ extra_attr in Html.summary ~a @@ anchor_link @ source (inline ~resolve) summary in [ Html.details ~a:open' summary included_html ] @@ -322,8 +317,8 @@ and items ~resolve l : item Html.elt list = let inc = [ Html.div ~a:[ Html.a_class a_class ] (doc @ content) ] in (continue_with [@tailcall]) rest inc | Declaration { Item.attr; anchor; content; doc } :: rest -> - let anchor_attrib, anchor_link = mk_anchor anchor in - let a = spec_class attr @ anchor_attrib in + let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let a = spec_class (attr @ extra_class) @ extra_attr in let content = anchor_link @ documentedSrc ~resolve content in let spec = let doc = spec_doc_div ~resolve doc in diff --git a/src/odoc/etc/odoc.css b/src/odoc/etc/odoc.css index 9bf2267d6e..4cbbfffcbd 100644 --- a/src/odoc/etc/odoc.css +++ b/src/odoc/etc/odoc.css @@ -419,8 +419,8 @@ pre code { padding: 0.35em 0.5em; } -.def-doc { - margin-bottom: 10px; +li:not(:last-child) > .def-doc { + margin-bottom: 15px; } /* Spacing between items */ @@ -428,19 +428,34 @@ div.odoc-spec,.odoc-include { margin-bottom: 2em; } -.spec.type .variant { +.spec.type .variant p, .spec.type .record p { + margin: 5px; +} + +.spec.type .variant, .spec.type .record { margin-left: 2ch; + list-style: none; + display: flex; + flex-wrap: wrap; + row-gap: 4px; } -.spec.type .variant p { - margin: 0; - font-style: italic; + +.spec.type .record > code, .spec.type .variant > code { + min-width: 40%; } -.spec.type .record { - margin-left: 2ch; + +.spec.type > ol { + margin-top: 0; + margin-bottom: 0; } -.spec.type .record p { - margin: 0; - font-style: italic; + +.spec.type .record > .def-doc, .spec.type .variant > .def-doc { + min-width:50%; + padding-left: 22px; + margin-left: 10%; + border-radius: 3px; + flex-grow:1; + border-left: 0.1em solid var(--spec-summary-border-color); } div.def { @@ -449,11 +464,6 @@ div.def { padding-left: 2ex; } -div.def+div.def-doc { - margin-left: 1ex; - margin-top: 2.5px -} - div.def-doc>*:first-child { margin-top: 0; } diff --git a/test/generators/html/Alias-X.html b/test/generators/html/Alias-X.html index 16211f07b0..d66a1eefbd 100644 --- a/test/generators/html/Alias-X.html +++ b/test/generators/html/Alias-X.html @@ -15,7 +15,7 @@

Module Alias.X

-
+
type t = int diff --git a/test/generators/html/Alias.html b/test/generators/html/Alias.html index 8b1900a638..12b4b96368 100644 --- a/test/generators/html/Alias.html +++ b/test/generators/html/Alias.html @@ -12,7 +12,7 @@

Module Alias

-
+
module X diff --git a/test/generators/html/Bugs.html b/test/generators/html/Bugs.html index dc716de80f..f17228f347 100644 --- a/test/generators/html/Bugs.html +++ b/test/generators/html/Bugs.html @@ -12,7 +12,7 @@

Module Bugs

-
+
type 'a opt = 'a option @@ -20,7 +20,7 @@

Module Bugs

-
+
val foo : diff --git a/test/generators/html/Bugs_post_406.html b/test/generators/html/Bugs_post_406.html index 73ca532ec8..682bb9bcd9 100644 --- a/test/generators/html/Bugs_post_406.html +++ b/test/generators/html/Bugs_post_406.html @@ -16,7 +16,7 @@

Module Bugs_post_406

-
+
class @@ -31,7 +31,7 @@

Module Bugs_post_406

-
+
class let_open' diff --git a/test/generators/html/Bugs_pre_410.html b/test/generators/html/Bugs_pre_410.html index 5078379897..091e0caebd 100644 --- a/test/generators/html/Bugs_pre_410.html +++ b/test/generators/html/Bugs_pre_410.html @@ -13,7 +13,7 @@

Module Bugs_pre_410

-
+
type 'a opt' @@ -22,7 +22,7 @@

Module Bugs_pre_410

-
+
val foo' : diff --git a/test/generators/html/Class.html b/test/generators/html/Class.html index 99af51a5bc..b76484dba5 100644 --- a/test/generators/html/Class.html +++ b/test/generators/html/Class.html @@ -12,7 +12,7 @@

Module Class

-
+
class @@ -25,7 +25,7 @@

Module Class

-
+
class @@ -39,7 +39,7 @@

Module Class

-
+
class @@ -53,7 +53,7 @@

Module Class

-
+
class mutually' @@ -62,7 +62,7 @@

Module Class

-
+
class recursive' @@ -71,8 +71,8 @@

Module Class

-
+
+ class type virtual @@ -87,7 +87,7 @@

Module Class

-
+
class @@ -99,7 +99,7 @@

Module Class

-
+
class @@ -114,7 +114,7 @@

Module Class

-
+
class 'a polymorphic' diff --git a/test/generators/html/External.html b/test/generators/html/External.html index bda7395d2f..6a6d1bd6e2 100644 --- a/test/generators/html/External.html +++ b/test/generators/html/External.html @@ -13,7 +13,7 @@

Module External

-
+
val foo : diff --git a/test/generators/html/Functor-F1-argument-1-Arg.html b/test/generators/html/Functor-F1-argument-1-Arg.html index 6f1fdddf7b..61ff7b2c10 100644 --- a/test/generators/html/Functor-F1-argument-1-Arg.html +++ b/test/generators/html/Functor-F1-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter F1.1-Arg

-
+
type t
diff --git a/test/generators/html/Functor-F1.html b/test/generators/html/Functor-F1.html index 4374fabfa6..94d2fd210c 100644 --- a/test/generators/html/Functor-F1.html +++ b/test/generators/html/Functor-F1.html @@ -22,7 +22,7 @@

Module Functor.F1

Parameters

-
+
module Arg @@ -32,7 +32,7 @@

Parameters

Signature

-
+
type t
diff --git a/test/generators/html/Functor-F2-argument-1-Arg.html b/test/generators/html/Functor-F2-argument-1-Arg.html index 566fbde26a..f9ad727c70 100644 --- a/test/generators/html/Functor-F2-argument-1-Arg.html +++ b/test/generators/html/Functor-F2-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter F2.1-Arg

-
+
type t
diff --git a/test/generators/html/Functor-F2.html b/test/generators/html/Functor-F2.html index 8569659e87..0aaa72fc94 100644 --- a/test/generators/html/Functor-F2.html +++ b/test/generators/html/Functor-F2.html @@ -22,7 +22,7 @@

Module Functor.F2

Parameters

-
+
module Arg @@ -32,7 +32,7 @@

Parameters

Signature

-
+
type t = Arg.t diff --git a/test/generators/html/Functor-F3-argument-1-Arg.html b/test/generators/html/Functor-F3-argument-1-Arg.html index ae9df67c95..04e9b90bc2 100644 --- a/test/generators/html/Functor-F3-argument-1-Arg.html +++ b/test/generators/html/Functor-F3-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter F3.1-Arg

-
+
type t
diff --git a/test/generators/html/Functor-F3.html b/test/generators/html/Functor-F3.html index eb8fa26a51..f3e65eb200 100644 --- a/test/generators/html/Functor-F3.html +++ b/test/generators/html/Functor-F3.html @@ -22,7 +22,7 @@

Module Functor.F3

Parameters

-
+
module Arg @@ -32,7 +32,7 @@

Parameters

Signature

-
+
type t = Arg.t diff --git a/test/generators/html/Functor-F4-argument-1-Arg.html b/test/generators/html/Functor-F4-argument-1-Arg.html index 06bbe6c3d9..016324ce3d 100644 --- a/test/generators/html/Functor-F4-argument-1-Arg.html +++ b/test/generators/html/Functor-F4-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter F4.1-Arg

-
+
type t
diff --git a/test/generators/html/Functor-F4.html b/test/generators/html/Functor-F4.html index fa74de1950..fbbb68ace5 100644 --- a/test/generators/html/Functor-F4.html +++ b/test/generators/html/Functor-F4.html @@ -22,7 +22,7 @@

Module Functor.F4

Parameters

-
+
module Arg @@ -32,7 +32,7 @@

Parameters

Signature

-
+
type t
diff --git a/test/generators/html/Functor-F5.html b/test/generators/html/Functor-F5.html index b476e8e7c7..779b851dc2 100644 --- a/test/generators/html/Functor-F5.html +++ b/test/generators/html/Functor-F5.html @@ -23,7 +23,7 @@

Parameters

Signature

-
+
type t
diff --git a/test/generators/html/Functor-module-type-S.html b/test/generators/html/Functor-module-type-S.html index c7ae05228e..e904fd4589 100644 --- a/test/generators/html/Functor-module-type-S.html +++ b/test/generators/html/Functor-module-type-S.html @@ -15,7 +15,7 @@

Module type Functor.S

-
+
type t
diff --git a/test/generators/html/Functor-module-type-S1-argument-1-_.html b/test/generators/html/Functor-module-type-S1-argument-1-_.html index ef0e8cd037..2926155df1 100644 --- a/test/generators/html/Functor-module-type-S1-argument-1-_.html +++ b/test/generators/html/Functor-module-type-S1-argument-1-_.html @@ -17,7 +17,7 @@

Parameter S1.1-_

-
+
type t
diff --git a/test/generators/html/Functor-module-type-S1.html b/test/generators/html/Functor-module-type-S1.html index 7564aaee5b..c6ff6b11c9 100644 --- a/test/generators/html/Functor-module-type-S1.html +++ b/test/generators/html/Functor-module-type-S1.html @@ -22,7 +22,7 @@

Module type Functor.S1

Parameters

-
+
module _ @@ -32,7 +32,7 @@

Parameters

Signature

-
+
type t
diff --git a/test/generators/html/Functor.html b/test/generators/html/Functor.html index 6ec1ff4001..06a1738ff5 100644 --- a/test/generators/html/Functor.html +++ b/test/generators/html/Functor.html @@ -13,7 +13,7 @@

Module Functor

-
+
module @@ -27,7 +27,7 @@

Module Functor

-
+
module @@ -44,7 +44,7 @@

Module Functor

-
+
module @@ -58,7 +58,7 @@

Module Functor

-
+
module @@ -77,7 +77,7 @@

Module Functor

-
+
module @@ -91,7 +91,7 @@

Module Functor

-
+
module @@ -105,7 +105,7 @@

Module Functor

-
+
module diff --git a/test/generators/html/Functor2-X-argument-1-Y.html b/test/generators/html/Functor2-X-argument-1-Y.html index 7c5a10e847..bef2e0eeb5 100644 --- a/test/generators/html/Functor2-X-argument-1-Y.html +++ b/test/generators/html/Functor2-X-argument-1-Y.html @@ -17,7 +17,7 @@

Parameter X.1-Y

-
+
type t
diff --git a/test/generators/html/Functor2-X-argument-2-Z.html b/test/generators/html/Functor2-X-argument-2-Z.html index 34503908cf..a4bb38497f 100644 --- a/test/generators/html/Functor2-X-argument-2-Z.html +++ b/test/generators/html/Functor2-X-argument-2-Z.html @@ -17,7 +17,7 @@

Parameter X.2-Z

-
+
type t
diff --git a/test/generators/html/Functor2-X.html b/test/generators/html/Functor2-X.html index 01e7a1aa23..d979923192 100644 --- a/test/generators/html/Functor2-X.html +++ b/test/generators/html/Functor2-X.html @@ -22,7 +22,7 @@

Module Functor2.X

Parameters

-
+
module Y @@ -31,7 +31,7 @@

Parameters

-
+
module Z @@ -41,7 +41,7 @@

Parameters

Signature

-
+
type y_t = Y.t @@ -49,7 +49,7 @@

Signature

-
+
type z_t = Z.t @@ -57,7 +57,7 @@

Signature

-
+
type x_t = y_t diff --git a/test/generators/html/Functor2-module-type-S.html b/test/generators/html/Functor2-module-type-S.html index f9af33d977..5c5bbb9857 100644 --- a/test/generators/html/Functor2-module-type-S.html +++ b/test/generators/html/Functor2-module-type-S.html @@ -15,7 +15,7 @@

Module type Functor2.S

-
+
type t
diff --git a/test/generators/html/Functor2-module-type-XF-argument-1-Y.html b/test/generators/html/Functor2-module-type-XF-argument-1-Y.html index e25c3fe51c..6ce6db27e8 100644 --- a/test/generators/html/Functor2-module-type-XF-argument-1-Y.html +++ b/test/generators/html/Functor2-module-type-XF-argument-1-Y.html @@ -17,7 +17,7 @@

Parameter XF.1-Y

-
+
type t
diff --git a/test/generators/html/Functor2-module-type-XF-argument-2-Z.html b/test/generators/html/Functor2-module-type-XF-argument-2-Z.html index b7852cda04..caf4277287 100644 --- a/test/generators/html/Functor2-module-type-XF-argument-2-Z.html +++ b/test/generators/html/Functor2-module-type-XF-argument-2-Z.html @@ -17,7 +17,7 @@

Parameter XF.2-Z

-
+
type t
diff --git a/test/generators/html/Functor2-module-type-XF.html b/test/generators/html/Functor2-module-type-XF.html index 6fc9b6cbfe..918c2a9f88 100644 --- a/test/generators/html/Functor2-module-type-XF.html +++ b/test/generators/html/Functor2-module-type-XF.html @@ -23,7 +23,7 @@

Module type Functor2.XF

Parameters

-
+
module Y @@ -32,7 +32,7 @@

Parameters

-
+
module Z @@ -42,7 +42,7 @@

Parameters

Signature

-
+
type y_t = @@ -52,7 +52,7 @@

Signature

-
+
type z_t = @@ -62,7 +62,7 @@

Signature

-
+
type x_t = y_t diff --git a/test/generators/html/Functor2.html b/test/generators/html/Functor2.html index cd3780c871..be8fbdbbeb 100644 --- a/test/generators/html/Functor2.html +++ b/test/generators/html/Functor2.html @@ -13,7 +13,7 @@

Module Functor2

-
+
module @@ -27,7 +27,7 @@

Module Functor2

-
+
module @@ -43,7 +43,7 @@

Module Functor2

-
+
module diff --git a/test/generators/html/Include-module-type-Dorminant_Module.html b/test/generators/html/Include-module-type-Dorminant_Module.html index 372f12900c..205aef9514 100644 --- a/test/generators/html/Include-module-type-Dorminant_Module.html +++ b/test/generators/html/Include-module-type-Dorminant_Module.html @@ -28,7 +28,7 @@

Module type Include.Dorminant_Module

-
+
val a : diff --git a/test/generators/html/Include-module-type-Inherent_Module.html b/test/generators/html/Include-module-type-Inherent_Module.html index f4d502d5f1..60cef3b722 100644 --- a/test/generators/html/Include-module-type-Inherent_Module.html +++ b/test/generators/html/Include-module-type-Inherent_Module.html @@ -16,7 +16,7 @@

Module type Include.Inherent_Module

-
+
val a : diff --git a/test/generators/html/Include-module-type-Inlined.html b/test/generators/html/Include-module-type-Inlined.html index 38ee80ccf3..3952b4fbbd 100644 --- a/test/generators/html/Include-module-type-Inlined.html +++ b/test/generators/html/Include-module-type-Inlined.html @@ -16,7 +16,7 @@

Module type Include.Inlined

-
+
type u
diff --git a/test/generators/html/Include-module-type-Not_inlined.html b/test/generators/html/Include-module-type-Not_inlined.html index 02f8bb787b..b1b1ce05b7 100644 --- a/test/generators/html/Include-module-type-Not_inlined.html +++ b/test/generators/html/Include-module-type-Not_inlined.html @@ -16,7 +16,7 @@

Module type Include.Not_inlined

-
+
type t
diff --git a/test/generators/html/Include-module-type-Not_inlined_and_closed.html b/test/generators/html/Include-module-type-Not_inlined_and_closed.html index a18903a118..f47df423d1 100644 --- a/test/generators/html/Include-module-type-Not_inlined_and_closed.html +++ b/test/generators/html/Include-module-type-Not_inlined_and_closed.html @@ -17,7 +17,7 @@

Module type Include.Not_inlined_and_closed
-
+
type v
diff --git a/test/generators/html/Include-module-type-Not_inlined_and_opened.html b/test/generators/html/Include-module-type-Not_inlined_and_opened.html index f6f16266b8..ccddf167e1 100644 --- a/test/generators/html/Include-module-type-Not_inlined_and_opened.html +++ b/test/generators/html/Include-module-type-Not_inlined_and_opened.html @@ -17,7 +17,7 @@

Module type Include.Not_inlined_and_opened
-
+
type w
diff --git a/test/generators/html/Include.html b/test/generators/html/Include.html index 759e52695f..fd98420248 100644 --- a/test/generators/html/Include.html +++ b/test/generators/html/Include.html @@ -13,8 +13,8 @@

Module Include

-
+
+ module type @@ -36,7 +36,7 @@

Module Include

-
+
type t
@@ -44,7 +44,7 @@

Module Include

-
+
module @@ -59,15 +59,15 @@

Module Include

-
+
type u
-
+
module @@ -94,7 +94,7 @@

Module Include

-
+
type v
@@ -102,8 +102,8 @@

Module Include

-
+
module @@ -130,7 +130,7 @@

Module Include

-
+
type w
@@ -138,8 +138,7 @@

Module Include

-
+
module @@ -165,8 +164,7 @@

Module Include

-
+
module @@ -203,7 +201,7 @@

Module Include

-
+
val a : u diff --git a/test/generators/html/Include2-X.html b/test/generators/html/Include2-X.html index 456361ca4f..735aaafbe7 100644 --- a/test/generators/html/Include2-X.html +++ b/test/generators/html/Include2-X.html @@ -16,7 +16,7 @@

Module Include2.X

-
+
type t = int diff --git a/test/generators/html/Include2-Y.html b/test/generators/html/Include2-Y.html index 01e0fe9cb7..cbfeed49f5 100644 --- a/test/generators/html/Include2-Y.html +++ b/test/generators/html/Include2-Y.html @@ -16,7 +16,7 @@

Module Include2.Y

-
+
type t
diff --git a/test/generators/html/Include2-Y_include_doc.html b/test/generators/html/Include2-Y_include_doc.html index ed554b29d2..747d46d7c5 100644 --- a/test/generators/html/Include2-Y_include_doc.html +++ b/test/generators/html/Include2-Y_include_doc.html @@ -33,7 +33,7 @@

Module Include2.Y_include_doc

-
+
type t = Y.t diff --git a/test/generators/html/Include2-Y_include_synopsis.html b/test/generators/html/Include2-Y_include_synopsis.html index 01eb9a3cb8..679ec6f5a3 100644 --- a/test/generators/html/Include2-Y_include_synopsis.html +++ b/test/generators/html/Include2-Y_include_synopsis.html @@ -31,7 +31,7 @@

Module Include2.Y_include_synopsis

-
+
type t = Y.t diff --git a/test/generators/html/Include2.html b/test/generators/html/Include2.html index 48ca8e68e7..6e9b2d3723 100644 --- a/test/generators/html/Include2.html +++ b/test/generators/html/Include2.html @@ -13,7 +13,7 @@

Module Include2

-
+
module @@ -42,7 +42,7 @@

Module Include2

Comment about X that should not appear when including X below.

-
+
type t = int @@ -52,7 +52,7 @@

Module Include2

-
+
module @@ -65,7 +65,7 @@

Module Include2

Top-comment of Y.

-
+
module @@ -83,7 +83,7 @@

Module Include2

-
+
module diff --git a/test/generators/html/Include_sections-module-type-Something.html b/test/generators/html/Include_sections-module-type-Something.html index 07b3300b9c..f31eee3462 100644 --- a/test/generators/html/Include_sections-module-type-Something.html +++ b/test/generators/html/Include_sections-module-type-Something.html @@ -24,7 +24,7 @@

Module type Include_sections.Something

-
+
val something : unit @@ -33,7 +33,7 @@

Module type Include_sections.Something

Something 1

foo

-
+
val foo : unit
@@ -41,7 +41,7 @@

Something 1

Something 2

-
+
val bar : unit

foo bar

diff --git a/test/generators/html/Include_sections.html b/test/generators/html/Include_sections.html index 55574d4a76..3a1fccfda0 100644 --- a/test/generators/html/Include_sections.html +++ b/test/generators/html/Include_sections.html @@ -34,7 +34,7 @@

Module Include_sections

-
+
module @@ -109,7 +109,7 @@

-
+
val something : unit @@ -119,7 +119,7 @@

Something 1

foo

-
+
val foo : unit
@@ -128,7 +128,7 @@

Something 2

-
+
val bar : unit

foo bar

diff --git a/test/generators/html/Interlude.html b/test/generators/html/Interlude.html index eb79c5bd32..56bcd71d48 100644 --- a/test/generators/html/Interlude.html +++ b/test/generators/html/Interlude.html @@ -15,7 +15,7 @@

Module Interlude

Some separate stray text at the top of the module.

-
+
val foo : unit

Foo.

@@ -24,27 +24,27 @@

Module Interlude

It has multiple paragraphs.

A separate block of stray text, adjacent to the preceding one.

-
+
val bar : unit

Bar.

-
+
val multiple : unit
-
+
val signature : unit
-
+
val items : unit
diff --git a/test/generators/html/Labels.html b/test/generators/html/Labels.html index 61cec92c38..8ebe6a778b 100644 --- a/test/generators/html/Labels.html +++ b/test/generators/html/Labels.html @@ -19,7 +19,7 @@

Module Labels

Attached to unit

Attached to nothing

-
+
module A @@ -31,13 +31,13 @@

Attached to nothing

-
+
type t

Attached to type

-
+
val f : t @@ -46,7 +46,7 @@

Attached to nothing

Attached to value

-
+
val e : @@ -57,7 +57,7 @@

Attached to nothing

Attached to external

-
+
module @@ -71,7 +71,7 @@

Attached to nothing

-
+
class c @@ -82,7 +82,7 @@

Attached to nothing

-
+
class @@ -95,7 +95,7 @@

Attached to nothing

-
+
exception E @@ -103,7 +103,7 @@

Attached to nothing

Attached to exception

-
+
type x = .. @@ -111,24 +111,23 @@

Attached to nothing

-
+
type x += - - - - -
- | X - -
+
    +
  1. + + | X + +
  2. +

Attached to extension

-
+
module S := @@ -138,7 +137,7 @@

Attached to nothing

Attached to module subst

-
+
type s := t @@ -146,40 +145,37 @@

Attached to nothing

Attached to type subst

-
+
type u = - - - - - -
- - | A' - - (* +
    +
  1. + + | A' + +
    (*

    Attached to constructor

    *) -
+
+ +
-
+
type v = { - - - - - -
- f : t; - (* +
    +
  1. + + f : t; +
    (*

    Attached to field

    *) -
} +
+ + }

Testing that labels can be referenced

  • Attached to unit
  • diff --git a/test/generators/html/Markup.html b/test/generators/html/Markup.html index d17a5cf7ce..8815b52b24 100644 --- a/test/generators/html/Markup.html +++ b/test/generators/html/Markup.html @@ -235,7 +235,7 @@

    Modules

  • version -1
-
+
val foo : unit
@@ -246,7 +246,7 @@

Modules

Some modules to support references.

-
+
module X @@ -258,7 +258,7 @@

Modules

-
+
module Y diff --git a/test/generators/html/Module-module-type-S.html b/test/generators/html/Module-module-type-S.html index 473074b065..8ee9d63cff 100644 --- a/test/generators/html/Module-module-type-S.html +++ b/test/generators/html/Module-module-type-S.html @@ -15,26 +15,26 @@

Module type Module.S

-
+
type t
-
+
type u
-
+
type 'a v
-
+
type ('a, 'b) w @@ -42,7 +42,7 @@

Module type Module.S

-
+
module diff --git a/test/generators/html/Module-module-type-S3.html b/test/generators/html/Module-module-type-S3.html index cc286c7352..068cb4c1b0 100644 --- a/test/generators/html/Module-module-type-S3.html +++ b/test/generators/html/Module-module-type-S3.html @@ -15,7 +15,7 @@

Module type Module.S3

-
+
type t = int @@ -23,7 +23,7 @@

Module type Module.S3

-
+
type u = string @@ -31,14 +31,14 @@

Module type Module.S3

-
+
type 'a v
-
+
type ('a, 'b) w @@ -46,7 +46,7 @@

Module type Module.S3

-
+
module diff --git a/test/generators/html/Module-module-type-S4.html b/test/generators/html/Module-module-type-S4.html index 90cf75a2c5..413716269a 100644 --- a/test/generators/html/Module-module-type-S4.html +++ b/test/generators/html/Module-module-type-S4.html @@ -15,20 +15,20 @@

Module type Module.S4

-
+
type u
-
+
type 'a v
-
+
type ('a, 'b) w @@ -36,7 +36,7 @@

Module type Module.S4

-
+
module diff --git a/test/generators/html/Module-module-type-S5.html b/test/generators/html/Module-module-type-S5.html index 756276bca7..73000364a7 100644 --- a/test/generators/html/Module-module-type-S5.html +++ b/test/generators/html/Module-module-type-S5.html @@ -15,19 +15,19 @@

Module type Module.S5

-
+
type t
-
+
type u
-
+
type ('a, 'b) w @@ -35,7 +35,7 @@

Module type Module.S5

-
+
module diff --git a/test/generators/html/Module-module-type-S6.html b/test/generators/html/Module-module-type-S6.html index 4ba1eaff17..2f21bb47dc 100644 --- a/test/generators/html/Module-module-type-S6.html +++ b/test/generators/html/Module-module-type-S6.html @@ -15,26 +15,26 @@

Module type Module.S6

-
+
type t
-
+
type u
-
+
type 'a v
-
+
module diff --git a/test/generators/html/Module-module-type-S7.html b/test/generators/html/Module-module-type-S7.html index ceb39ddc9e..c0803ca6be 100644 --- a/test/generators/html/Module-module-type-S7.html +++ b/test/generators/html/Module-module-type-S7.html @@ -15,26 +15,26 @@

Module type Module.S7

-
+
type t
-
+
type u
-
+
type 'a v
-
+
type ('a, 'b) w @@ -42,7 +42,7 @@

Module type Module.S7

-
+
module M = M' diff --git a/test/generators/html/Module-module-type-S8.html b/test/generators/html/Module-module-type-S8.html index 6e063616bb..55c05ace22 100644 --- a/test/generators/html/Module-module-type-S8.html +++ b/test/generators/html/Module-module-type-S8.html @@ -15,26 +15,26 @@

Module type Module.S8

-
+
type t
-
+
type u
-
+
type 'a v
-
+
type ('a, 'b) w diff --git a/test/generators/html/Module.html b/test/generators/html/Module.html index 09a04039f4..35b4d66333 100644 --- a/test/generators/html/Module.html +++ b/test/generators/html/Module.html @@ -12,7 +12,7 @@

Module Module

Foo.

-
+
val foo : unit
@@ -26,7 +26,7 @@

Module Module

Foo.

-
+
module @@ -40,7 +40,7 @@

Module Module

Foo.

-
+
module @@ -50,7 +50,7 @@

Module Module

Foo.

-
+
module @@ -60,7 +60,7 @@

Module Module

Foo.

-
+
module @@ -80,7 +80,7 @@

Module Module

Foo.

-
+
module @@ -97,7 +97,7 @@

Module Module

Foo.

-
+
module @@ -115,7 +115,7 @@

Module Module

Foo.

-
+
type ('a, 'b) result @@ -124,7 +124,7 @@

Module Module

Foo.

-
+
module @@ -147,7 +147,7 @@

Module Module

Foo.

-
+
module @@ -160,7 +160,7 @@

Module Module

Foo.

-
+
module @@ -178,7 +178,7 @@

Module Module

Foo.

-
+
module @@ -196,7 +196,7 @@

Module Module

Foo.

-
+
module @@ -211,7 +211,7 @@

Module Module

Foo.

-
+
module @@ -224,7 +224,7 @@

Module Module

Foo.

-
+
module diff --git a/test/generators/html/Module_type_alias-module-type-A.html b/test/generators/html/Module_type_alias-module-type-A.html index 9151e3535a..444a9b0e5b 100644 --- a/test/generators/html/Module_type_alias-module-type-A.html +++ b/test/generators/html/Module_type_alias-module-type-A.html @@ -16,7 +16,7 @@

Module type Module_type_alias.A

-
+
type a
diff --git a/test/generators/html/Module_type_alias-module-type-B-argument-1-C.html b/test/generators/html/Module_type_alias-module-type-B-argument-1-C.html index ad27463656..c8eaf1a066 100644 --- a/test/generators/html/Module_type_alias-module-type-B-argument-1-C.html +++ b/test/generators/html/Module_type_alias-module-type-B-argument-1-C.html @@ -17,7 +17,7 @@

Parameter B.1-C

-
+
type c
diff --git a/test/generators/html/Module_type_alias-module-type-B.html b/test/generators/html/Module_type_alias-module-type-B.html index 18d782b86e..c02e14b538 100644 --- a/test/generators/html/Module_type_alias-module-type-B.html +++ b/test/generators/html/Module_type_alias-module-type-B.html @@ -23,7 +23,7 @@

Module type Module_type_alias.B

Parameters

-
+
module C @@ -36,7 +36,7 @@

Parameters

Signature

-
+
type b
diff --git a/test/generators/html/Module_type_alias-module-type-E-argument-1-F.html b/test/generators/html/Module_type_alias-module-type-E-argument-1-F.html index 9365e25aab..2e9acf2a07 100644 --- a/test/generators/html/Module_type_alias-module-type-E-argument-1-F.html +++ b/test/generators/html/Module_type_alias-module-type-E-argument-1-F.html @@ -17,7 +17,7 @@

Parameter E.1-F

-
+
type f
diff --git a/test/generators/html/Module_type_alias-module-type-E-argument-2-C.html b/test/generators/html/Module_type_alias-module-type-E-argument-2-C.html index 775b4168f2..3436bf7753 100644 --- a/test/generators/html/Module_type_alias-module-type-E-argument-2-C.html +++ b/test/generators/html/Module_type_alias-module-type-E-argument-2-C.html @@ -17,7 +17,7 @@

Parameter E.2-C

-
+
type c
diff --git a/test/generators/html/Module_type_alias-module-type-E.html b/test/generators/html/Module_type_alias-module-type-E.html index 67544fb6f2..6ae49cfc94 100644 --- a/test/generators/html/Module_type_alias-module-type-E.html +++ b/test/generators/html/Module_type_alias-module-type-E.html @@ -23,7 +23,7 @@

Module type Module_type_alias.E

Parameters

-
+
module F @@ -35,7 +35,7 @@

Parameters

-
+
module C @@ -48,7 +48,7 @@

Parameters

Signature

-
+
type b
diff --git a/test/generators/html/Module_type_alias-module-type-G-argument-1-H.html b/test/generators/html/Module_type_alias-module-type-G-argument-1-H.html index ffaae01f55..2240a03c34 100644 --- a/test/generators/html/Module_type_alias-module-type-G-argument-1-H.html +++ b/test/generators/html/Module_type_alias-module-type-G-argument-1-H.html @@ -17,7 +17,7 @@

Parameter G.1-H

-
+
type h
diff --git a/test/generators/html/Module_type_alias-module-type-G.html b/test/generators/html/Module_type_alias-module-type-G.html index 486a1e6a14..12133bebac 100644 --- a/test/generators/html/Module_type_alias-module-type-G.html +++ b/test/generators/html/Module_type_alias-module-type-G.html @@ -23,7 +23,7 @@

Module type Module_type_alias.G

Parameters

-
+
module H @@ -36,7 +36,7 @@

Parameters

Signature

-
+
type a
diff --git a/test/generators/html/Module_type_alias.html b/test/generators/html/Module_type_alias.html index 783e186e20..7c8ed79f3e 100644 --- a/test/generators/html/Module_type_alias.html +++ b/test/generators/html/Module_type_alias.html @@ -14,7 +14,7 @@

Module Module_type_alias

-
+
module @@ -28,7 +28,7 @@

Module Module_type_alias

-
+
module @@ -48,7 +48,7 @@

Module Module_type_alias

-
+
module @@ -59,7 +59,7 @@

Module Module_type_alias

-
+
module @@ -78,7 +78,7 @@

Module Module_type_alias

-
+
module @@ -97,7 +97,7 @@

Module Module_type_alias

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic-module-type-a.html b/test/generators/html/Module_type_subst-Basic-module-type-a.html index 3b03a68837..a3d00488f1 100644 --- a/test/generators/html/Module_type_subst-Basic-module-type-a.html +++ b/test/generators/html/Module_type_subst-Basic-module-type-a.html @@ -17,7 +17,7 @@

Module type Basic.a

-
+
module @@ -28,7 +28,7 @@

Module type Basic.a

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic-module-type-c.html b/test/generators/html/Module_type_subst-Basic-module-type-c.html index 92bbe54e91..c7954104e5 100644 --- a/test/generators/html/Module_type_subst-Basic-module-type-c.html +++ b/test/generators/html/Module_type_subst-Basic-module-type-c.html @@ -17,7 +17,7 @@

Module type Basic.c

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic-module-type-u.html b/test/generators/html/Module_type_subst-Basic-module-type-u.html index 067b41ac1d..f27c696e34 100644 --- a/test/generators/html/Module_type_subst-Basic-module-type-u.html +++ b/test/generators/html/Module_type_subst-Basic-module-type-u.html @@ -17,7 +17,7 @@

Module type Basic.u

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic-module-type-u2.html b/test/generators/html/Module_type_subst-Basic-module-type-u2.html index 924a82d5a0..3fdf25e4ca 100644 --- a/test/generators/html/Module_type_subst-Basic-module-type-u2.html +++ b/test/generators/html/Module_type_subst-Basic-module-type-u2.html @@ -17,7 +17,7 @@

Module type Basic.u2

-
+
module @@ -32,7 +32,7 @@

Module type Basic.u2

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic-module-type-with_.html b/test/generators/html/Module_type_subst-Basic-module-type-with_.html index 3f1c7ee18a..0368ac69a8 100644 --- a/test/generators/html/Module_type_subst-Basic-module-type-with_.html +++ b/test/generators/html/Module_type_subst-Basic-module-type-with_.html @@ -17,7 +17,7 @@

Module type Basic.with_

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic-module-type-with_2.html b/test/generators/html/Module_type_subst-Basic-module-type-with_2.html index 0277847489..13734999d4 100644 --- a/test/generators/html/Module_type_subst-Basic-module-type-with_2.html +++ b/test/generators/html/Module_type_subst-Basic-module-type-with_2.html @@ -17,7 +17,7 @@

Module type Basic.with_2

-
+
module @@ -34,7 +34,7 @@

Module type Basic.with_2

-
+
module diff --git a/test/generators/html/Module_type_subst-Basic.html b/test/generators/html/Module_type_subst-Basic.html index d46d1fc503..e3fee2ff5c 100644 --- a/test/generators/html/Module_type_subst-Basic.html +++ b/test/generators/html/Module_type_subst-Basic.html @@ -16,7 +16,7 @@

Module Module_type_subst.Basic

-
+
module @@ -30,7 +30,7 @@

Module Module_type_subst.Basic

-
+
module @@ -49,7 +49,7 @@

Module Module_type_subst.Basic

-
+
module @@ -63,7 +63,7 @@

Module Module_type_subst.Basic

-
+
module @@ -83,7 +83,7 @@

Module Module_type_subst.Basic

-
+
module @@ -97,7 +97,7 @@

Module Module_type_subst.Basic

-
+
module diff --git a/test/generators/html/Module_type_subst-Local-module-type-local.html b/test/generators/html/Module_type_subst-Local-module-type-local.html index c2b59eef3f..9ce1a43a11 100644 --- a/test/generators/html/Module_type_subst-Local-module-type-local.html +++ b/test/generators/html/Module_type_subst-Local-module-type-local.html @@ -17,7 +17,7 @@

Module type Local.local

-
+
type t = local diff --git a/test/generators/html/Module_type_subst-Local.html b/test/generators/html/Module_type_subst-Local.html index 964ade6f63..20f44873f7 100644 --- a/test/generators/html/Module_type_subst-Local.html +++ b/test/generators/html/Module_type_subst-Local.html @@ -16,7 +16,7 @@

Module Module_type_subst.Local

-
+
type local := int * int @@ -24,7 +24,7 @@

Module Module_type_subst.Local

-
+
module @@ -38,7 +38,7 @@

Module Module_type_subst.Local

-
+
module @@ -51,7 +51,7 @@

Module Module_type_subst.Local

-
+
module diff --git a/test/generators/html/Module_type_subst-Nested-module-type-nested-N.html b/test/generators/html/Module_type_subst-Nested-module-type-nested-N.html index 0923e87450..e74295bd74 100644 --- a/test/generators/html/Module_type_subst-Nested-module-type-nested-N.html +++ b/test/generators/html/Module_type_subst-Nested-module-type-nested-N.html @@ -20,7 +20,7 @@

Module nested.N

-
+
module diff --git a/test/generators/html/Module_type_subst-Nested-module-type-nested.html b/test/generators/html/Module_type_subst-Nested-module-type-nested.html index 64891911f3..b4fdfcb9bc 100644 --- a/test/generators/html/Module_type_subst-Nested-module-type-nested.html +++ b/test/generators/html/Module_type_subst-Nested-module-type-nested.html @@ -17,7 +17,7 @@

Module type Nested.nested

-
+
module diff --git a/test/generators/html/Module_type_subst-Nested-module-type-with_-N.html b/test/generators/html/Module_type_subst-Nested-module-type-with_-N.html index 8e0188672c..0f143f0b9b 100644 --- a/test/generators/html/Module_type_subst-Nested-module-type-with_-N.html +++ b/test/generators/html/Module_type_subst-Nested-module-type-with_-N.html @@ -20,7 +20,7 @@

Module with_.N

-
+
module diff --git a/test/generators/html/Module_type_subst-Nested-module-type-with_.html b/test/generators/html/Module_type_subst-Nested-module-type-with_.html index fec32fd31d..cfd7db223c 100644 --- a/test/generators/html/Module_type_subst-Nested-module-type-with_.html +++ b/test/generators/html/Module_type_subst-Nested-module-type-with_.html @@ -17,7 +17,7 @@

Module type Nested.with_

-
+
module diff --git a/test/generators/html/Module_type_subst-Nested-module-type-with_subst.html b/test/generators/html/Module_type_subst-Nested-module-type-with_subst.html index 3c83bf7d5c..c05828bd29 100644 --- a/test/generators/html/Module_type_subst-Nested-module-type-with_subst.html +++ b/test/generators/html/Module_type_subst-Nested-module-type-with_subst.html @@ -17,7 +17,7 @@

Module type Nested.with_subst

-
+
module diff --git a/test/generators/html/Module_type_subst-Nested.html b/test/generators/html/Module_type_subst-Nested.html index ceb4edd764..3d83ea65ef 100644 --- a/test/generators/html/Module_type_subst-Nested.html +++ b/test/generators/html/Module_type_subst-Nested.html @@ -16,7 +16,7 @@

Module Module_type_subst.Nested

-
+
module @@ -30,7 +30,7 @@

Module Module_type_subst.Nested

-
+
module @@ -52,8 +52,8 @@

Module Module_type_subst.Nested

-
+
+ module type diff --git a/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c.html b/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c.html index a28a1249e7..b62cfd7c07 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c.html @@ -28,22 +28,20 @@

Module type b.c

-
+
type t = - - - - -
- - | - A - of t - - -
+
    +
  1. + + | + A + of t + + +
  2. +
diff --git a/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b.html b/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b.html index c681a6ad71..237d71aebc 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a-module-type-b.html @@ -22,7 +22,7 @@

Module type a.b

-
+
module diff --git a/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a.html b/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a.html index 80af85b047..d6abbbc196 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-u-module-type-a.html @@ -20,7 +20,7 @@

Module type u.a

-
+
module diff --git a/test/generators/html/Module_type_subst-Structural-module-type-u.html b/test/generators/html/Module_type_subst-Structural-module-type-u.html index 058dd16129..3a18f59bf0 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-u.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-u.html @@ -18,7 +18,7 @@

Module type Structural.u

-
+
module diff --git a/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c.html b/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c.html index 3fd7d7c2d0..72753d06f4 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c.html @@ -28,22 +28,20 @@

Module type b.c

-
+
type t = - - - - -
- - | - A - of t - - -
+
    +
  1. + + | + A + of t + + +
  2. +
diff --git a/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b.html b/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b.html index 25bf254340..5d88defa81 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a-module-type-b.html @@ -22,7 +22,7 @@

Module type a.b

-
+
module diff --git a/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a.html b/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a.html index 150fc0fa21..1033b78388 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-w-module-type-a.html @@ -20,7 +20,7 @@

Module type w.a

-
+
module diff --git a/test/generators/html/Module_type_subst-Structural-module-type-w.html b/test/generators/html/Module_type_subst-Structural-module-type-w.html index f315f4e021..293fc947f7 100644 --- a/test/generators/html/Module_type_subst-Structural-module-type-w.html +++ b/test/generators/html/Module_type_subst-Structural-module-type-w.html @@ -18,7 +18,7 @@

Module type Structural.w

-
+
module diff --git a/test/generators/html/Module_type_subst-Structural.html b/test/generators/html/Module_type_subst-Structural.html index ba1c690565..5e0f5872d8 100644 --- a/test/generators/html/Module_type_subst-Structural.html +++ b/test/generators/html/Module_type_subst-Structural.html @@ -16,7 +16,7 @@

Module Module_type_subst.Structural

-
+
module @@ -30,7 +30,7 @@

Module Module_type_subst.Structural

-
+
module diff --git a/test/generators/html/Module_type_subst.html b/test/generators/html/Module_type_subst.html index e7cee85ab3..27d07006d5 100644 --- a/test/generators/html/Module_type_subst.html +++ b/test/generators/html/Module_type_subst.html @@ -13,7 +13,7 @@

Module Module_type_subst

-
+
module @@ -26,7 +26,7 @@

Module Module_type_subst

-
+
module @@ -40,7 +40,7 @@

Module Module_type_subst

-
+
module @@ -53,7 +53,7 @@

Module Module_type_subst

-
+
module @@ -66,7 +66,7 @@

Module Module_type_subst

-
+
module diff --git a/test/generators/html/Nested-F-argument-1-Arg1.html b/test/generators/html/Nested-F-argument-1-Arg1.html index 327238cddb..13be09fe69 100644 --- a/test/generators/html/Nested-F-argument-1-Arg1.html +++ b/test/generators/html/Nested-F-argument-1-Arg1.html @@ -22,13 +22,13 @@

Parameter F.1-Arg1

Type

-
+
type t

Some type.

Values

-
+
val y : t diff --git a/test/generators/html/Nested-F-argument-2-Arg2.html b/test/generators/html/Nested-F-argument-2-Arg2.html index 7f816f2e33..30d0f6ce52 100644 --- a/test/generators/html/Nested-F-argument-2-Arg2.html +++ b/test/generators/html/Nested-F-argument-2-Arg2.html @@ -19,7 +19,7 @@

Parameter F.2-Arg2

Type

-
+
type t

Some type.

diff --git a/test/generators/html/Nested-F.html b/test/generators/html/Nested-F.html index 3990c519fc..0c79007a1c 100644 --- a/test/generators/html/Nested-F.html +++ b/test/generators/html/Nested-F.html @@ -24,7 +24,7 @@

Module Nested.F

Parameters

-
+
module Arg1 @@ -33,7 +33,7 @@

Parameters

-
+
module Arg2 @@ -46,7 +46,7 @@

Parameters

Signature

Type

-
+
type t = Arg1.t diff --git a/test/generators/html/Nested-X.html b/test/generators/html/Nested-X.html index 374a159c19..5244f82bb8 100644 --- a/test/generators/html/Nested-X.html +++ b/test/generators/html/Nested-X.html @@ -21,13 +21,13 @@

Module Nested.X

This is module X.

Type

-
+
type t

Some type.

Values

-
+
val x : t diff --git a/test/generators/html/Nested-class-z.html b/test/generators/html/Nested-class-z.html index 619abc4a23..de187def3b 100644 --- a/test/generators/html/Nested-class-z.html +++ b/test/generators/html/Nested-class-z.html @@ -18,13 +18,13 @@

Class Nested.z

This is class z.

-
+
val y : int

Some value.

-
+
val @@ -35,13 +35,13 @@

Class Nested.z

This is class z.

Methods

-
+
method z : int

Some method.

-
+
method diff --git a/test/generators/html/Nested-module-type-Y.html b/test/generators/html/Nested-module-type-Y.html index 2da9d0b2a3..862d9ea4fd 100644 --- a/test/generators/html/Nested-module-type-Y.html +++ b/test/generators/html/Nested-module-type-Y.html @@ -21,13 +21,13 @@

Module type Nested.Y

Type

-
+
type t

Some type.

Values

-
+
val y : t diff --git a/test/generators/html/Nested.html b/test/generators/html/Nested.html index dd019b5c53..73c0100879 100644 --- a/test/generators/html/Nested.html +++ b/test/generators/html/Nested.html @@ -21,7 +21,7 @@

Module Nested

Module

-
+
module X @@ -35,7 +35,7 @@

Module

Module type

-
+
module @@ -49,7 +49,7 @@

Module type

This is module type Y.

Functor

-
+
module F @@ -65,7 +65,7 @@

Module type

This is a functor F.

Class

-
+
class @@ -78,7 +78,7 @@

Module type

This is class z.

-
+
class diff --git a/test/generators/html/Ocamlary-Aliases-E.html b/test/generators/html/Ocamlary-Aliases-E.html index 56983ba541..7334638258 100644 --- a/test/generators/html/Ocamlary-Aliases-E.html +++ b/test/generators/html/Ocamlary-Aliases-E.html @@ -17,13 +17,13 @@

Module Aliases.E

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-Foo-A.html b/test/generators/html/Ocamlary-Aliases-Foo-A.html index ad9173f775..e0a6ee154b 100644 --- a/test/generators/html/Ocamlary-Aliases-Foo-A.html +++ b/test/generators/html/Ocamlary-Aliases-Foo-A.html @@ -18,13 +18,13 @@

Module Foo.A

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-Foo-B.html b/test/generators/html/Ocamlary-Aliases-Foo-B.html index dd854e4c15..61f52fdd7c 100644 --- a/test/generators/html/Ocamlary-Aliases-Foo-B.html +++ b/test/generators/html/Ocamlary-Aliases-Foo-B.html @@ -18,13 +18,13 @@

Module Foo.B

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-Foo-C.html b/test/generators/html/Ocamlary-Aliases-Foo-C.html index fa299ebe44..d352d912e0 100644 --- a/test/generators/html/Ocamlary-Aliases-Foo-C.html +++ b/test/generators/html/Ocamlary-Aliases-Foo-C.html @@ -18,13 +18,13 @@

Module Foo.C

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-Foo-D.html b/test/generators/html/Ocamlary-Aliases-Foo-D.html index 9b02c1306c..f78b0b97c0 100644 --- a/test/generators/html/Ocamlary-Aliases-Foo-D.html +++ b/test/generators/html/Ocamlary-Aliases-Foo-D.html @@ -18,13 +18,13 @@

Module Foo.D

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-Foo-E.html b/test/generators/html/Ocamlary-Aliases-Foo-E.html index 10ee26ec92..fd4ce6a71c 100644 --- a/test/generators/html/Ocamlary-Aliases-Foo-E.html +++ b/test/generators/html/Ocamlary-Aliases-Foo-E.html @@ -18,13 +18,13 @@

Module Foo.E

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-Foo.html b/test/generators/html/Ocamlary-Aliases-Foo.html index 02ba7a8529..bcea060eb1 100644 --- a/test/generators/html/Ocamlary-Aliases-Foo.html +++ b/test/generators/html/Ocamlary-Aliases-Foo.html @@ -17,7 +17,7 @@

Module Aliases.Foo

-
+
module @@ -30,7 +30,7 @@

Module Aliases.Foo

-
+
module @@ -43,7 +43,7 @@

Module Aliases.Foo

-
+
module @@ -56,7 +56,7 @@

Module Aliases.Foo

-
+
module @@ -69,7 +69,7 @@

Module Aliases.Foo

-
+
module diff --git a/test/generators/html/Ocamlary-Aliases-P1-Y.html b/test/generators/html/Ocamlary-Aliases-P1-Y.html index ec14340191..75b86cf7d6 100644 --- a/test/generators/html/Ocamlary-Aliases-P1-Y.html +++ b/test/generators/html/Ocamlary-Aliases-P1-Y.html @@ -18,13 +18,13 @@

Module P1.Y

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-P1.html b/test/generators/html/Ocamlary-Aliases-P1.html index 663ea97c6f..d875a62519 100644 --- a/test/generators/html/Ocamlary-Aliases-P1.html +++ b/test/generators/html/Ocamlary-Aliases-P1.html @@ -17,7 +17,7 @@

Module Aliases.P1

-
+
module diff --git a/test/generators/html/Ocamlary-Aliases-P2-Z.html b/test/generators/html/Ocamlary-Aliases-P2-Z.html index 32950443cc..b97946d4a0 100644 --- a/test/generators/html/Ocamlary-Aliases-P2-Z.html +++ b/test/generators/html/Ocamlary-Aliases-P2-Z.html @@ -18,13 +18,13 @@

Module P2.Z

-
+
type t
-
+
val id : diff --git a/test/generators/html/Ocamlary-Aliases-P2.html b/test/generators/html/Ocamlary-Aliases-P2.html index f713afbde9..e69eb94b97 100644 --- a/test/generators/html/Ocamlary-Aliases-P2.html +++ b/test/generators/html/Ocamlary-Aliases-P2.html @@ -17,7 +17,7 @@

Module Aliases.P2

-
+
module diff --git a/test/generators/html/Ocamlary-Aliases-Std.html b/test/generators/html/Ocamlary-Aliases-Std.html index afdc32979b..e6c70c69ad 100644 --- a/test/generators/html/Ocamlary-Aliases-Std.html +++ b/test/generators/html/Ocamlary-Aliases-Std.html @@ -17,7 +17,7 @@

Module Aliases.Std

-
+
module A = Foo.A @@ -25,7 +25,7 @@

Module Aliases.Std

-
+
module B = Foo.B @@ -33,7 +33,7 @@

Module Aliases.Std

-
+
module C = Foo.C @@ -41,7 +41,7 @@

Module Aliases.Std

-
+
module D = Foo.D @@ -49,7 +49,7 @@

Module Aliases.Std

-
+
module E = Foo.E diff --git a/test/generators/html/Ocamlary-Aliases.html b/test/generators/html/Ocamlary-Aliases.html index 7b2b09dee2..5534e269af 100644 --- a/test/generators/html/Ocamlary-Aliases.html +++ b/test/generators/html/Ocamlary-Aliases.html @@ -19,7 +19,7 @@

Module Ocamlary.Aliases

-
+
module @@ -32,7 +32,7 @@

Module Ocamlary.Aliases

-
+
module A' = Foo.A @@ -40,7 +40,7 @@

Module Ocamlary.Aliases

-
+
type tata = Foo.A.t @@ -49,7 +49,7 @@

Module Ocamlary.Aliases

-
+
type tbtb = Foo.B.t @@ -58,13 +58,13 @@

Module Ocamlary.Aliases

-
+
type tete
-
+
type tata' = A'.t @@ -72,7 +72,7 @@

Module Ocamlary.Aliases

-
+
type tete2 = Foo.E.t @@ -81,7 +81,7 @@

Module Ocamlary.Aliases

-
+
module @@ -94,7 +94,7 @@

Module Ocamlary.Aliases

-
+
type stde = Std.E.t @@ -117,7 +117,7 @@

Module Ocamlary.Aliases

-
+
module A = Foo.A @@ -125,7 +125,7 @@

Module Ocamlary.Aliases

-
+
module B = Foo.B @@ -133,7 +133,7 @@

Module Ocamlary.Aliases

-
+
module C = Foo.C @@ -141,7 +141,7 @@

Module Ocamlary.Aliases

-
+
module D = Foo.D @@ -149,7 +149,7 @@

Module Ocamlary.Aliases

-
+
module @@ -164,7 +164,7 @@

Module Ocamlary.Aliases

-
+
type testa = A.t @@ -177,7 +177,7 @@

Module Ocamlary.Aliases

Foo.B.id

-
+
module @@ -190,7 +190,7 @@

Module Ocamlary.Aliases

-
+
module @@ -203,7 +203,7 @@

Module Ocamlary.Aliases

-
+
module X1 = P2.Z @@ -211,7 +211,7 @@

Module Ocamlary.Aliases

-
+
module X2 = P2.Z @@ -219,7 +219,7 @@

Module Ocamlary.Aliases

-
+
type p1 = X1.t @@ -227,7 +227,7 @@

Module Ocamlary.Aliases

-
+
type p2 = X2.t diff --git a/test/generators/html/Ocamlary-Buffer.html b/test/generators/html/Ocamlary-Buffer.html index 997125084a..baf890671d 100644 --- a/test/generators/html/Ocamlary-Buffer.html +++ b/test/generators/html/Ocamlary-Buffer.html @@ -19,7 +19,7 @@

Module Ocamlary.Buffer

-
+
val f : diff --git a/test/generators/html/Ocamlary-CanonicalTest-Base-List.html b/test/generators/html/Ocamlary-CanonicalTest-Base-List.html index 2cc953b7a8..dbe3de8c08 100644 --- a/test/generators/html/Ocamlary-CanonicalTest-Base-List.html +++ b/test/generators/html/Ocamlary-CanonicalTest-Base-List.html @@ -18,14 +18,14 @@

Module Base.List

-
+
type 'a t
-
+
val id : diff --git a/test/generators/html/Ocamlary-CanonicalTest-Base.html b/test/generators/html/Ocamlary-CanonicalTest-Base.html index 26fe220c0e..fb107f08f8 100644 --- a/test/generators/html/Ocamlary-CanonicalTest-Base.html +++ b/test/generators/html/Ocamlary-CanonicalTest-Base.html @@ -17,7 +17,7 @@

Module CanonicalTest.Base

-
+
module diff --git a/test/generators/html/Ocamlary-CanonicalTest-Base_Tests-C.html b/test/generators/html/Ocamlary-CanonicalTest-Base_Tests-C.html index 239bb39afa..a58930d2a3 100644 --- a/test/generators/html/Ocamlary-CanonicalTest-Base_Tests-C.html +++ b/test/generators/html/Ocamlary-CanonicalTest-Base_Tests-C.html @@ -20,14 +20,14 @@

Module Base_Tests.C

-
+
type 'a t
-
+
val id : diff --git a/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html b/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html index 5a2b73964a..466f042a2e 100644 --- a/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html +++ b/test/generators/html/Ocamlary-CanonicalTest-Base_Tests.html @@ -18,7 +18,7 @@

Module CanonicalTest.Base_Tests

-
+
module @@ -32,7 +32,7 @@

Module CanonicalTest.Base_Tests

-
+
module L = Base.List @@ -41,7 +41,7 @@

Module CanonicalTest.Base_Tests

-
+
val foo : @@ -58,7 +58,7 @@

Module CanonicalTest.Base_Tests

-
+
val bar : @@ -77,7 +77,7 @@

Module CanonicalTest.Base_Tests

-
+
val baz : diff --git a/test/generators/html/Ocamlary-CanonicalTest-List_modif.html b/test/generators/html/Ocamlary-CanonicalTest-List_modif.html index 0751d65d83..c45e6f0114 100644 --- a/test/generators/html/Ocamlary-CanonicalTest-List_modif.html +++ b/test/generators/html/Ocamlary-CanonicalTest-List_modif.html @@ -18,7 +18,7 @@

Module CanonicalTest.List_modif

-
+
type 'c t = @@ -31,7 +31,7 @@

Module CanonicalTest.List_modif

-
+
val id : diff --git a/test/generators/html/Ocamlary-CanonicalTest.html b/test/generators/html/Ocamlary-CanonicalTest.html index 419cf98f33..274a90f0d9 100644 --- a/test/generators/html/Ocamlary-CanonicalTest.html +++ b/test/generators/html/Ocamlary-CanonicalTest.html @@ -16,7 +16,7 @@

Module Ocamlary.CanonicalTest

-
+
module @@ -29,7 +29,7 @@

Module Ocamlary.CanonicalTest

-
+
module @@ -42,7 +42,7 @@

Module Ocamlary.CanonicalTest

-
+
module diff --git a/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html index 1f1a20bbe8..8125936706 100644 --- a/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html @@ -22,7 +22,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html index b9c76e552c..981a59f02e 100644 --- a/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -24,7 +24,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-CollectionModule-InnerModuleA.html b/test/generators/html/Ocamlary-CollectionModule-InnerModuleA.html index a6f06a4f5f..ebf754c58d 100644 --- a/test/generators/html/Ocamlary-CollectionModule-InnerModuleA.html +++ b/test/generators/html/Ocamlary-CollectionModule-InnerModuleA.html @@ -19,7 +19,7 @@

Module CollectionModule.InnerModuleA

-
+
type t = @@ -31,7 +31,7 @@

Module CollectionModule.InnerModuleA

This comment is for t.

-
+
module @@ -49,8 +49,7 @@

Module CollectionModule.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-CollectionModule.html b/test/generators/html/Ocamlary-CollectionModule.html index d51809a64e..e41e474d57 100644 --- a/test/generators/html/Ocamlary-CollectionModule.html +++ b/test/generators/html/Ocamlary-CollectionModule.html @@ -17,7 +17,7 @@

Module Ocamlary.CollectionModule

-
+
type collection
@@ -25,13 +25,13 @@

Module Ocamlary.CollectionModule

-
+
type element
-
+
module @@ -47,8 +47,7 @@

Module Ocamlary.CollectionModule

-
+
module diff --git a/test/generators/html/Ocamlary-Dep1-X-Y-class-c.html b/test/generators/html/Ocamlary-Dep1-X-Y-class-c.html index 3fa746f648..c0b81e7da9 100644 --- a/test/generators/html/Ocamlary-Dep1-X-Y-class-c.html +++ b/test/generators/html/Ocamlary-Dep1-X-Y-class-c.html @@ -18,7 +18,7 @@
-
+
method m : int
diff --git a/test/generators/html/Ocamlary-Dep1-X-Y.html b/test/generators/html/Ocamlary-Dep1-X-Y.html index d1e97e124a..f59a4dfef7 100644 --- a/test/generators/html/Ocamlary-Dep1-X-Y.html +++ b/test/generators/html/Ocamlary-Dep1-X-Y.html @@ -17,7 +17,7 @@
-
+
class c diff --git a/test/generators/html/Ocamlary-Dep1-X.html b/test/generators/html/Ocamlary-Dep1-X.html index 1feb6d4a50..acfb0980b6 100644 --- a/test/generators/html/Ocamlary-Dep1-X.html +++ b/test/generators/html/Ocamlary-Dep1-X.html @@ -17,7 +17,7 @@

Module Dep1.X

-
+
module diff --git a/test/generators/html/Ocamlary-Dep1-module-type-S-class-c.html b/test/generators/html/Ocamlary-Dep1-module-type-S-class-c.html index ee7ddd5efc..9184cb412f 100644 --- a/test/generators/html/Ocamlary-Dep1-module-type-S-class-c.html +++ b/test/generators/html/Ocamlary-Dep1-module-type-S-class-c.html @@ -17,7 +17,7 @@
-
+
method m : int
diff --git a/test/generators/html/Ocamlary-Dep1-module-type-S.html b/test/generators/html/Ocamlary-Dep1-module-type-S.html index 5e4047f6e4..eecbca345e 100644 --- a/test/generators/html/Ocamlary-Dep1-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep1-module-type-S.html @@ -17,7 +17,7 @@

Module type Dep1.S

-
+
class c diff --git a/test/generators/html/Ocamlary-Dep1.html b/test/generators/html/Ocamlary-Dep1.html index f87082b287..ba65872045 100644 --- a/test/generators/html/Ocamlary-Dep1.html +++ b/test/generators/html/Ocamlary-Dep1.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep1

-
+
module @@ -30,7 +30,7 @@

Module Ocamlary.Dep1

-
+
module diff --git a/test/generators/html/Ocamlary-Dep11-module-type-S-class-c.html b/test/generators/html/Ocamlary-Dep11-module-type-S-class-c.html index b801e82d0d..ae0cd5fd00 100644 --- a/test/generators/html/Ocamlary-Dep11-module-type-S-class-c.html +++ b/test/generators/html/Ocamlary-Dep11-module-type-S-class-c.html @@ -17,7 +17,7 @@
-
+
method m : int
diff --git a/test/generators/html/Ocamlary-Dep11-module-type-S.html b/test/generators/html/Ocamlary-Dep11-module-type-S.html index 207c445c81..e140427cb9 100644 --- a/test/generators/html/Ocamlary-Dep11-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep11-module-type-S.html @@ -17,7 +17,7 @@

Module type Dep11.S

-
+
class c diff --git a/test/generators/html/Ocamlary-Dep11.html b/test/generators/html/Ocamlary-Dep11.html index 8698fae22c..192bca702c 100644 --- a/test/generators/html/Ocamlary-Dep11.html +++ b/test/generators/html/Ocamlary-Dep11.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep11

-
+
module diff --git a/test/generators/html/Ocamlary-Dep12-argument-1-Arg.html b/test/generators/html/Ocamlary-Dep12-argument-1-Arg.html index 910f6e42c9..d18e185f56 100644 --- a/test/generators/html/Ocamlary-Dep12-argument-1-Arg.html +++ b/test/generators/html/Ocamlary-Dep12-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter Dep12.1-Arg

-
+
module diff --git a/test/generators/html/Ocamlary-Dep12.html b/test/generators/html/Ocamlary-Dep12.html index 42661b5ec4..71d9f7f7a3 100644 --- a/test/generators/html/Ocamlary-Dep12.html +++ b/test/generators/html/Ocamlary-Dep12.html @@ -23,7 +23,7 @@

Module Ocamlary.Dep12

Parameters

-
+
module Arg @@ -35,7 +35,7 @@

Parameters

Signature

-
+
module diff --git a/test/generators/html/Ocamlary-Dep13-class-c.html b/test/generators/html/Ocamlary-Dep13-class-c.html index edf4524531..e34549e278 100644 --- a/test/generators/html/Ocamlary-Dep13-class-c.html +++ b/test/generators/html/Ocamlary-Dep13-class-c.html @@ -17,7 +17,7 @@

Class Dep13.c

-
+
method m : int
diff --git a/test/generators/html/Ocamlary-Dep13.html b/test/generators/html/Ocamlary-Dep13.html index bd42910855..d62ee51139 100644 --- a/test/generators/html/Ocamlary-Dep13.html +++ b/test/generators/html/Ocamlary-Dep13.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep13

-
+
class c diff --git a/test/generators/html/Ocamlary-Dep2-A.html b/test/generators/html/Ocamlary-Dep2-A.html index feb3f0f338..0bdbb2882f 100644 --- a/test/generators/html/Ocamlary-Dep2-A.html +++ b/test/generators/html/Ocamlary-Dep2-A.html @@ -17,7 +17,7 @@

Module Dep2.A

-
+
module Y : diff --git a/test/generators/html/Ocamlary-Dep2-argument-1-Arg-X.html b/test/generators/html/Ocamlary-Dep2-argument-1-Arg-X.html index 6c00cfa200..3c0266f0d0 100644 --- a/test/generators/html/Ocamlary-Dep2-argument-1-Arg-X.html +++ b/test/generators/html/Ocamlary-Dep2-argument-1-Arg-X.html @@ -18,7 +18,7 @@

Module 1-Arg.X

-
+
module Y : diff --git a/test/generators/html/Ocamlary-Dep2-argument-1-Arg.html b/test/generators/html/Ocamlary-Dep2-argument-1-Arg.html index 921e410f27..5bced3466b 100644 --- a/test/generators/html/Ocamlary-Dep2-argument-1-Arg.html +++ b/test/generators/html/Ocamlary-Dep2-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter Dep2.1-Arg

-
+
module @@ -27,7 +27,7 @@

Parameter Dep2.1-Arg

-
+
module diff --git a/test/generators/html/Ocamlary-Dep2.html b/test/generators/html/Ocamlary-Dep2.html index 371fd0b2de..cc34a0171f 100644 --- a/test/generators/html/Ocamlary-Dep2.html +++ b/test/generators/html/Ocamlary-Dep2.html @@ -23,7 +23,7 @@

Module Ocamlary.Dep2

Parameters

-
+
module Arg @@ -35,7 +35,7 @@

Parameters

Signature

-
+
module @@ -48,7 +48,7 @@

Signature

-
+
module B = A.Y diff --git a/test/generators/html/Ocamlary-Dep3.html b/test/generators/html/Ocamlary-Dep3.html index debfb480eb..6ce7cfe0a7 100644 --- a/test/generators/html/Ocamlary-Dep3.html +++ b/test/generators/html/Ocamlary-Dep3.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep3

-
+
type a
diff --git a/test/generators/html/Ocamlary-Dep4-X.html b/test/generators/html/Ocamlary-Dep4-X.html index 43224540b0..fedfe167d9 100644 --- a/test/generators/html/Ocamlary-Dep4-X.html +++ b/test/generators/html/Ocamlary-Dep4-X.html @@ -17,7 +17,7 @@

Module Dep4.X

-
+
type b
diff --git a/test/generators/html/Ocamlary-Dep4-module-type-S-X.html b/test/generators/html/Ocamlary-Dep4-module-type-S-X.html index 70643fe674..29008e40a5 100644 --- a/test/generators/html/Ocamlary-Dep4-module-type-S-X.html +++ b/test/generators/html/Ocamlary-Dep4-module-type-S-X.html @@ -17,7 +17,7 @@
-
+
type b
diff --git a/test/generators/html/Ocamlary-Dep4-module-type-S.html b/test/generators/html/Ocamlary-Dep4-module-type-S.html index 6b26f1e092..2cc2348d0e 100644 --- a/test/generators/html/Ocamlary-Dep4-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep4-module-type-S.html @@ -17,7 +17,7 @@

Module type Dep4.S

-
+
module @@ -27,7 +27,7 @@

Module type Dep4.S

-
+
module diff --git a/test/generators/html/Ocamlary-Dep4-module-type-T.html b/test/generators/html/Ocamlary-Dep4-module-type-T.html index 1e4d2ea3a0..d1775546b0 100644 --- a/test/generators/html/Ocamlary-Dep4-module-type-T.html +++ b/test/generators/html/Ocamlary-Dep4-module-type-T.html @@ -17,7 +17,7 @@

Module type Dep4.T

-
+
type b
diff --git a/test/generators/html/Ocamlary-Dep4.html b/test/generators/html/Ocamlary-Dep4.html index 40a3c71bc7..c2b63e3172 100644 --- a/test/generators/html/Ocamlary-Dep4.html +++ b/test/generators/html/Ocamlary-Dep4.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep4

-
+
module @@ -30,7 +30,7 @@

Module Ocamlary.Dep4

-
+
module @@ -44,7 +44,7 @@

Module Ocamlary.Dep4

-
+
module diff --git a/test/generators/html/Ocamlary-Dep5-Z.html b/test/generators/html/Ocamlary-Dep5-Z.html index 9bb0347c60..faf9c6f4a3 100644 --- a/test/generators/html/Ocamlary-Dep5-Z.html +++ b/test/generators/html/Ocamlary-Dep5-Z.html @@ -17,7 +17,7 @@

Module Dep5.Z

-
+
module X : @@ -27,7 +27,7 @@

Module Dep5.Z

-
+
module Y = Dep3 diff --git a/test/generators/html/Ocamlary-Dep5-argument-1-Arg-module-type-S.html b/test/generators/html/Ocamlary-Dep5-argument-1-Arg-module-type-S.html index 95d8f599a7..0637380201 100644 --- a/test/generators/html/Ocamlary-Dep5-argument-1-Arg-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep5-argument-1-Arg-module-type-S.html @@ -18,7 +18,7 @@

Module type 1-Arg.S

-
+
module X : @@ -28,7 +28,7 @@

Module type 1-Arg.S

-
+
module diff --git a/test/generators/html/Ocamlary-Dep5-argument-1-Arg.html b/test/generators/html/Ocamlary-Dep5-argument-1-Arg.html index 9701c238fc..15eb216858 100644 --- a/test/generators/html/Ocamlary-Dep5-argument-1-Arg.html +++ b/test/generators/html/Ocamlary-Dep5-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter Dep5.1-Arg

-
+
module @@ -27,7 +27,7 @@

Parameter Dep5.1-Arg

-
+
module @@ -41,7 +41,7 @@

Parameter Dep5.1-Arg

-
+
module X : T diff --git a/test/generators/html/Ocamlary-Dep5.html b/test/generators/html/Ocamlary-Dep5.html index 2efd5e6c38..647d0369b8 100644 --- a/test/generators/html/Ocamlary-Dep5.html +++ b/test/generators/html/Ocamlary-Dep5.html @@ -23,7 +23,7 @@

Module Ocamlary.Dep5

Parameters

-
+
module Arg @@ -35,7 +35,7 @@

Parameters

Signature

-
+
module diff --git a/test/generators/html/Ocamlary-Dep6-X-Y.html b/test/generators/html/Ocamlary-Dep6-X-Y.html index 8d5be8485d..6bd9e71961 100644 --- a/test/generators/html/Ocamlary-Dep6-X-Y.html +++ b/test/generators/html/Ocamlary-Dep6-X-Y.html @@ -17,7 +17,7 @@
-
+
type d
diff --git a/test/generators/html/Ocamlary-Dep6-X.html b/test/generators/html/Ocamlary-Dep6-X.html index 418d622c81..8feabe9f16 100644 --- a/test/generators/html/Ocamlary-Dep6-X.html +++ b/test/generators/html/Ocamlary-Dep6-X.html @@ -17,7 +17,7 @@

Module Dep6.X

-
+
module @@ -27,7 +27,7 @@

Module Dep6.X

-
+
module diff --git a/test/generators/html/Ocamlary-Dep6-module-type-S.html b/test/generators/html/Ocamlary-Dep6-module-type-S.html index 50374f4612..2f4f017478 100644 --- a/test/generators/html/Ocamlary-Dep6-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep6-module-type-S.html @@ -17,7 +17,7 @@

Module type Dep6.S

-
+
type d
diff --git a/test/generators/html/Ocamlary-Dep6-module-type-T-Y.html b/test/generators/html/Ocamlary-Dep6-module-type-T-Y.html index 84189084ea..5048d8ed83 100644 --- a/test/generators/html/Ocamlary-Dep6-module-type-T-Y.html +++ b/test/generators/html/Ocamlary-Dep6-module-type-T-Y.html @@ -17,7 +17,7 @@
-
+
type d
diff --git a/test/generators/html/Ocamlary-Dep6-module-type-T.html b/test/generators/html/Ocamlary-Dep6-module-type-T.html index f6183741c1..4fdd860764 100644 --- a/test/generators/html/Ocamlary-Dep6-module-type-T.html +++ b/test/generators/html/Ocamlary-Dep6-module-type-T.html @@ -17,7 +17,7 @@

Module type Dep6.T

-
+
module @@ -27,7 +27,7 @@

Module type Dep6.T

-
+
module diff --git a/test/generators/html/Ocamlary-Dep6.html b/test/generators/html/Ocamlary-Dep6.html index 719786e2eb..07f7eae03e 100644 --- a/test/generators/html/Ocamlary-Dep6.html +++ b/test/generators/html/Ocamlary-Dep6.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep6

-
+
module @@ -30,7 +30,7 @@

Module Ocamlary.Dep6

-
+
module @@ -44,7 +44,7 @@

Module Ocamlary.Dep6

-
+
module diff --git a/test/generators/html/Ocamlary-Dep7-M.html b/test/generators/html/Ocamlary-Dep7-M.html index 6aa3a46857..2aab9824af 100644 --- a/test/generators/html/Ocamlary-Dep7-M.html +++ b/test/generators/html/Ocamlary-Dep7-M.html @@ -17,7 +17,7 @@

Module Dep7.M

-
+
module @@ -30,7 +30,7 @@

Module Dep7.M

-
+
module Y : diff --git a/test/generators/html/Ocamlary-Dep7-argument-1-Arg-X.html b/test/generators/html/Ocamlary-Dep7-argument-1-Arg-X.html index a22f7b8ada..26ca9a7084 100644 --- a/test/generators/html/Ocamlary-Dep7-argument-1-Arg-X.html +++ b/test/generators/html/Ocamlary-Dep7-argument-1-Arg-X.html @@ -18,7 +18,7 @@

Module 1-Arg.X

-
+
module @@ -31,7 +31,7 @@

Module 1-Arg.X

-
+
module Y : diff --git a/test/generators/html/Ocamlary-Dep7-argument-1-Arg-module-type-T.html b/test/generators/html/Ocamlary-Dep7-argument-1-Arg-module-type-T.html index 8028c2c609..6014914e2d 100644 --- a/test/generators/html/Ocamlary-Dep7-argument-1-Arg-module-type-T.html +++ b/test/generators/html/Ocamlary-Dep7-argument-1-Arg-module-type-T.html @@ -18,7 +18,7 @@

Module type 1-Arg.T

-
+
module @@ -31,7 +31,7 @@

Module type 1-Arg.T

-
+
module Y : diff --git a/test/generators/html/Ocamlary-Dep7-argument-1-Arg.html b/test/generators/html/Ocamlary-Dep7-argument-1-Arg.html index 0bae0cff62..1316160709 100644 --- a/test/generators/html/Ocamlary-Dep7-argument-1-Arg.html +++ b/test/generators/html/Ocamlary-Dep7-argument-1-Arg.html @@ -17,7 +17,7 @@

Parameter Dep7.1-Arg

-
+
module @@ -27,7 +27,7 @@

Parameter Dep7.1-Arg

-
+
module @@ -41,7 +41,7 @@

Parameter Dep7.1-Arg

-
+
module diff --git a/test/generators/html/Ocamlary-Dep7.html b/test/generators/html/Ocamlary-Dep7.html index 0852e49660..62a56a8883 100644 --- a/test/generators/html/Ocamlary-Dep7.html +++ b/test/generators/html/Ocamlary-Dep7.html @@ -23,7 +23,7 @@

Module Ocamlary.Dep7

Parameters

-
+
module Arg @@ -35,7 +35,7 @@

Parameters

Signature

-
+
module diff --git a/test/generators/html/Ocamlary-Dep8-module-type-T.html b/test/generators/html/Ocamlary-Dep8-module-type-T.html index 0d916dddf6..a74159a068 100644 --- a/test/generators/html/Ocamlary-Dep8-module-type-T.html +++ b/test/generators/html/Ocamlary-Dep8-module-type-T.html @@ -17,7 +17,7 @@

Module type Dep8.T

-
+
type t
diff --git a/test/generators/html/Ocamlary-Dep8.html b/test/generators/html/Ocamlary-Dep8.html index 862192d6ff..60207a2303 100644 --- a/test/generators/html/Ocamlary-Dep8.html +++ b/test/generators/html/Ocamlary-Dep8.html @@ -16,7 +16,7 @@

Module Ocamlary.Dep8

-
+
module diff --git a/test/generators/html/Ocamlary-Dep9-argument-1-X.html b/test/generators/html/Ocamlary-Dep9-argument-1-X.html index c13518518f..d8cd3de249 100644 --- a/test/generators/html/Ocamlary-Dep9-argument-1-X.html +++ b/test/generators/html/Ocamlary-Dep9-argument-1-X.html @@ -17,7 +17,7 @@

Parameter Dep9.1-X

-
+
module diff --git a/test/generators/html/Ocamlary-Dep9.html b/test/generators/html/Ocamlary-Dep9.html index d733a95962..96bddd527e 100644 --- a/test/generators/html/Ocamlary-Dep9.html +++ b/test/generators/html/Ocamlary-Dep9.html @@ -23,7 +23,7 @@

Module Ocamlary.Dep9

Parameters

-
+
module X @@ -35,7 +35,7 @@

Parameters

Signature

-
+
module diff --git a/test/generators/html/Ocamlary-DoubleInclude1-DoubleInclude2.html b/test/generators/html/Ocamlary-DoubleInclude1-DoubleInclude2.html index 74c99c1a3d..a723e0d805 100644 --- a/test/generators/html/Ocamlary-DoubleInclude1-DoubleInclude2.html +++ b/test/generators/html/Ocamlary-DoubleInclude1-DoubleInclude2.html @@ -18,7 +18,7 @@

Module DoubleInclude1.DoubleInclude2

-
+
type double_include diff --git a/test/generators/html/Ocamlary-DoubleInclude1.html b/test/generators/html/Ocamlary-DoubleInclude1.html index d4b0715bff..d854299946 100644 --- a/test/generators/html/Ocamlary-DoubleInclude1.html +++ b/test/generators/html/Ocamlary-DoubleInclude1.html @@ -16,7 +16,7 @@

Module Ocamlary.DoubleInclude1

-
+
module diff --git a/test/generators/html/Ocamlary-DoubleInclude3-DoubleInclude2.html b/test/generators/html/Ocamlary-DoubleInclude3-DoubleInclude2.html index 35f9578b22..9297b45fc5 100644 --- a/test/generators/html/Ocamlary-DoubleInclude3-DoubleInclude2.html +++ b/test/generators/html/Ocamlary-DoubleInclude3-DoubleInclude2.html @@ -18,7 +18,7 @@

Module DoubleInclude3.DoubleInclude2

-
+
type double_include diff --git a/test/generators/html/Ocamlary-DoubleInclude3.html b/test/generators/html/Ocamlary-DoubleInclude3.html index bea58db2f7..caabf13e64 100644 --- a/test/generators/html/Ocamlary-DoubleInclude3.html +++ b/test/generators/html/Ocamlary-DoubleInclude3.html @@ -27,7 +27,7 @@

Module Ocamlary.DoubleInclude3

-
+
module diff --git a/test/generators/html/Ocamlary-ExtMod.html b/test/generators/html/Ocamlary-ExtMod.html index 4c9b4c83e9..300fbffbe4 100644 --- a/test/generators/html/Ocamlary-ExtMod.html +++ b/test/generators/html/Ocamlary-ExtMod.html @@ -16,7 +16,7 @@

Module Ocamlary.ExtMod

-
+
type t = .. @@ -24,23 +24,21 @@

Module Ocamlary.ExtMod

-
+
type t += - - - - -
- - | - Leisureforce - -
+
    +
  1. + + | + Leisureforce + +
  2. +
diff --git a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html index ffb91b5a86..2f6229fc77 100644 --- a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html @@ -28,7 +28,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html index eb51583267..3ea61320c3 100644 --- a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -28,7 +28,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html index 19a61238d3..e6208382f8 100644 --- a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html +++ b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html @@ -22,7 +22,7 @@

Module 1-Collection.InnerModuleA

-
+
type t = @@ -36,7 +36,7 @@

Module 1-Collection.InnerModuleA

This comment is for t.

-
+
module @@ -55,8 +55,7 @@

Module 1-Collection.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection.html b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection.html index 68e7ec3764..5c6add0340 100644 --- a/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection.html +++ b/test/generators/html/Ocamlary-FunctorTypeOf-argument-1-Collection.html @@ -19,7 +19,7 @@

Parameter FunctorTypeOf.1-Collection

This comment is for CollectionModule.

-
+
type collection
@@ -27,13 +27,13 @@

Parameter FunctorTypeOf.1-Collection

-
+
type element
-
+
module @@ -52,8 +52,7 @@

Parameter FunctorTypeOf.1-Collection

-
+
module diff --git a/test/generators/html/Ocamlary-FunctorTypeOf.html b/test/generators/html/Ocamlary-FunctorTypeOf.html index 05e4f40b12..d40b7230ed 100644 --- a/test/generators/html/Ocamlary-FunctorTypeOf.html +++ b/test/generators/html/Ocamlary-FunctorTypeOf.html @@ -24,7 +24,7 @@

Module Ocamlary.FunctorTypeOf

Parameters

-
+
module @@ -40,7 +40,7 @@

Parameters

Signature

-
+
type t = diff --git a/test/generators/html/Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html b/test/generators/html/Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html index 1c4e4e764f..e1fe6f4103 100644 --- a/test/generators/html/Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html +++ b/test/generators/html/Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html @@ -20,7 +20,7 @@

Module type IncludeInclude1.IncludeInclude2
-
+
type include_include diff --git a/test/generators/html/Ocamlary-IncludeInclude1.html b/test/generators/html/Ocamlary-IncludeInclude1.html index bcb211bb54..948887f7a9 100644 --- a/test/generators/html/Ocamlary-IncludeInclude1.html +++ b/test/generators/html/Ocamlary-IncludeInclude1.html @@ -16,8 +16,7 @@

Module Ocamlary.IncludeInclude1

-
+
module @@ -33,7 +32,7 @@

Module Ocamlary.IncludeInclude1

-
+
module diff --git a/test/generators/html/Ocamlary-IncludedA.html b/test/generators/html/Ocamlary-IncludedA.html index 2ddc2650d3..2abaf48837 100644 --- a/test/generators/html/Ocamlary-IncludedA.html +++ b/test/generators/html/Ocamlary-IncludedA.html @@ -16,7 +16,7 @@

Module Ocamlary.IncludedA

-
+
type t
diff --git a/test/generators/html/Ocamlary-M.html b/test/generators/html/Ocamlary-M.html index 3b8b26c8cc..bd5a987937 100644 --- a/test/generators/html/Ocamlary-M.html +++ b/test/generators/html/Ocamlary-M.html @@ -15,7 +15,7 @@

Module Ocamlary.M

-
+
type t
diff --git a/test/generators/html/Ocamlary-One.html b/test/generators/html/Ocamlary-One.html index 1e38d90b96..424c6a073c 100644 --- a/test/generators/html/Ocamlary-One.html +++ b/test/generators/html/Ocamlary-One.html @@ -16,7 +16,7 @@

Module Ocamlary.One

-
+
type one
diff --git a/test/generators/html/Ocamlary-Only_a_module.html b/test/generators/html/Ocamlary-Only_a_module.html index 672c6c2524..d334cb7b6a 100644 --- a/test/generators/html/Ocamlary-Only_a_module.html +++ b/test/generators/html/Ocamlary-Only_a_module.html @@ -16,7 +16,7 @@

Module Ocamlary.Only_a_module

-
+
type t
diff --git a/test/generators/html/Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html index 58fce3be27..02fa3cc98e 100644 --- a/test/generators/html/Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html @@ -22,7 +22,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html index f11a448f52..dee5e7bca2 100644 --- a/test/generators/html/Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -23,7 +23,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-Recollection-InnerModuleA.html b/test/generators/html/Ocamlary-Recollection-InnerModuleA.html index 4c39fb5fce..bc45eaf204 100644 --- a/test/generators/html/Ocamlary-Recollection-InnerModuleA.html +++ b/test/generators/html/Ocamlary-Recollection-InnerModuleA.html @@ -19,7 +19,7 @@

Module Recollection.InnerModuleA

-
+
type t = @@ -30,7 +30,7 @@

Module Recollection.InnerModuleA

This comment is for t.

-
+
module @@ -48,8 +48,7 @@

Module Recollection.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html index ebd3521aaf..38260cb532 100644 --- a/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html @@ -25,7 +25,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html index 8dde648054..e573ec46bf 100644 --- a/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -27,7 +27,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA.html b/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA.html index 1cfe9f1270..f5628fbdba 100644 --- a/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA.html +++ b/test/generators/html/Ocamlary-Recollection-argument-1-C-InnerModuleA.html @@ -21,7 +21,7 @@

Module 1-C.InnerModuleA

-
+
type t = @@ -34,7 +34,7 @@

Module 1-C.InnerModuleA

This comment is for t.

-
+
module @@ -53,8 +53,7 @@

Module 1-C.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-Recollection-argument-1-C.html b/test/generators/html/Ocamlary-Recollection-argument-1-C.html index 1b77ab6dae..5614a138d0 100644 --- a/test/generators/html/Ocamlary-Recollection-argument-1-C.html +++ b/test/generators/html/Ocamlary-Recollection-argument-1-C.html @@ -18,7 +18,7 @@

Parameter Recollection.1-C

This comment is for CollectionModule.

-
+
type collection
@@ -26,13 +26,13 @@

Parameter Recollection.1-C

-
+
type element
-
+
module @@ -50,8 +50,7 @@

Parameter Recollection.1-C

-
+
module diff --git a/test/generators/html/Ocamlary-Recollection.html b/test/generators/html/Ocamlary-Recollection.html index 65d197c3b7..65ed3a310a 100644 --- a/test/generators/html/Ocamlary-Recollection.html +++ b/test/generators/html/Ocamlary-Recollection.html @@ -23,7 +23,7 @@

Module Ocamlary.Recollection

Parameters

-
+
module C @@ -35,7 +35,7 @@

Parameters

Signature

This comment is for CollectionModule.

-
+
type collection = @@ -51,7 +51,7 @@

Signature

-
+
type element = @@ -63,7 +63,7 @@

Signature

-
+
module @@ -79,8 +79,7 @@

Signature

-
+
module diff --git a/test/generators/html/Ocamlary-With10-module-type-T-M.html b/test/generators/html/Ocamlary-With10-module-type-T-M.html index 3592d27ed2..9964e1a016 100644 --- a/test/generators/html/Ocamlary-With10-module-type-T-M.html +++ b/test/generators/html/Ocamlary-With10-module-type-T-M.html @@ -17,7 +17,7 @@
-
+
module diff --git a/test/generators/html/Ocamlary-With10-module-type-T.html b/test/generators/html/Ocamlary-With10-module-type-T.html index 0574863253..5693703f5f 100644 --- a/test/generators/html/Ocamlary-With10-module-type-T.html +++ b/test/generators/html/Ocamlary-With10-module-type-T.html @@ -18,7 +18,7 @@

Module type With10.T

-
+
module @@ -31,7 +31,7 @@

Module type With10.T

-
+
module N : diff --git a/test/generators/html/Ocamlary-With10.html b/test/generators/html/Ocamlary-With10.html index dafb57d1f9..0bac898abe 100644 --- a/test/generators/html/Ocamlary-With10.html +++ b/test/generators/html/Ocamlary-With10.html @@ -16,7 +16,7 @@

Module Ocamlary.With10

-
+
module diff --git a/test/generators/html/Ocamlary-With2-module-type-S.html b/test/generators/html/Ocamlary-With2-module-type-S.html index e7466bbfe2..b6b246c205 100644 --- a/test/generators/html/Ocamlary-With2-module-type-S.html +++ b/test/generators/html/Ocamlary-With2-module-type-S.html @@ -17,7 +17,7 @@

Module type With2.S

-
+
type t
diff --git a/test/generators/html/Ocamlary-With2.html b/test/generators/html/Ocamlary-With2.html index 70cc761b31..8cf242eeb1 100644 --- a/test/generators/html/Ocamlary-With2.html +++ b/test/generators/html/Ocamlary-With2.html @@ -16,7 +16,7 @@

Module Ocamlary.With2

-
+
module diff --git a/test/generators/html/Ocamlary-With3-N.html b/test/generators/html/Ocamlary-With3-N.html index 731d696df0..5a2e0eecd5 100644 --- a/test/generators/html/Ocamlary-With3-N.html +++ b/test/generators/html/Ocamlary-With3-N.html @@ -17,7 +17,7 @@

Module With3.N

-
+
type t
diff --git a/test/generators/html/Ocamlary-With3.html b/test/generators/html/Ocamlary-With3.html index fe8609d920..7fb53b9c57 100644 --- a/test/generators/html/Ocamlary-With3.html +++ b/test/generators/html/Ocamlary-With3.html @@ -16,7 +16,7 @@

Module Ocamlary.With3

-
+
module M = With2 @@ -24,7 +24,7 @@

Module Ocamlary.With3

-
+
module diff --git a/test/generators/html/Ocamlary-With4-N.html b/test/generators/html/Ocamlary-With4-N.html index 1eb8af4776..639ebf43fb 100644 --- a/test/generators/html/Ocamlary-With4-N.html +++ b/test/generators/html/Ocamlary-With4-N.html @@ -17,7 +17,7 @@

Module With4.N

-
+
type t
diff --git a/test/generators/html/Ocamlary-With4.html b/test/generators/html/Ocamlary-With4.html index da2e3bb205..705c080ce0 100644 --- a/test/generators/html/Ocamlary-With4.html +++ b/test/generators/html/Ocamlary-With4.html @@ -16,7 +16,7 @@

Module Ocamlary.With4

-
+
module diff --git a/test/generators/html/Ocamlary-With5-N.html b/test/generators/html/Ocamlary-With5-N.html index 3adf464161..b2d3dbc0e2 100644 --- a/test/generators/html/Ocamlary-With5-N.html +++ b/test/generators/html/Ocamlary-With5-N.html @@ -17,7 +17,7 @@

Module With5.N

-
+
type t
diff --git a/test/generators/html/Ocamlary-With5-module-type-S.html b/test/generators/html/Ocamlary-With5-module-type-S.html index dfc3ace923..1da57f3465 100644 --- a/test/generators/html/Ocamlary-With5-module-type-S.html +++ b/test/generators/html/Ocamlary-With5-module-type-S.html @@ -17,7 +17,7 @@

Module type With5.S

-
+
type t
diff --git a/test/generators/html/Ocamlary-With5.html b/test/generators/html/Ocamlary-With5.html index 6ed1c55bd3..0a900f3593 100644 --- a/test/generators/html/Ocamlary-With5.html +++ b/test/generators/html/Ocamlary-With5.html @@ -16,7 +16,7 @@

Module Ocamlary.With5

-
+
module @@ -30,7 +30,7 @@

Module Ocamlary.With5

-
+
module diff --git a/test/generators/html/Ocamlary-With6-module-type-T-M.html b/test/generators/html/Ocamlary-With6-module-type-T-M.html index 365323f0ba..fce0863ebb 100644 --- a/test/generators/html/Ocamlary-With6-module-type-T-M.html +++ b/test/generators/html/Ocamlary-With6-module-type-T-M.html @@ -17,7 +17,7 @@
-
+
module @@ -27,7 +27,7 @@
-
+
module N : S diff --git a/test/generators/html/Ocamlary-With6-module-type-T.html b/test/generators/html/Ocamlary-With6-module-type-T.html index dc69e6be6e..79aaf1961d 100644 --- a/test/generators/html/Ocamlary-With6-module-type-T.html +++ b/test/generators/html/Ocamlary-With6-module-type-T.html @@ -17,7 +17,7 @@

Module type With6.T

-
+
module diff --git a/test/generators/html/Ocamlary-With6.html b/test/generators/html/Ocamlary-With6.html index 506d01ba5f..5cdd55aa06 100644 --- a/test/generators/html/Ocamlary-With6.html +++ b/test/generators/html/Ocamlary-With6.html @@ -16,7 +16,7 @@

Module Ocamlary.With6

-
+
module diff --git a/test/generators/html/Ocamlary-With7-argument-1-X.html b/test/generators/html/Ocamlary-With7-argument-1-X.html index ac5c5e9b1a..44844b6930 100644 --- a/test/generators/html/Ocamlary-With7-argument-1-X.html +++ b/test/generators/html/Ocamlary-With7-argument-1-X.html @@ -17,7 +17,7 @@

Parameter With7.1-X

-
+
module diff --git a/test/generators/html/Ocamlary-With7.html b/test/generators/html/Ocamlary-With7.html index 8376558df3..040f01c637 100644 --- a/test/generators/html/Ocamlary-With7.html +++ b/test/generators/html/Ocamlary-With7.html @@ -23,7 +23,7 @@

Module Ocamlary.With7

Parameters

-
+
module X @@ -35,7 +35,7 @@

Parameters

Signature

-
+
module diff --git a/test/generators/html/Ocamlary-With9-module-type-S.html b/test/generators/html/Ocamlary-With9-module-type-S.html index 30130f58ae..c986b69e82 100644 --- a/test/generators/html/Ocamlary-With9-module-type-S.html +++ b/test/generators/html/Ocamlary-With9-module-type-S.html @@ -17,7 +17,7 @@

Module type With9.S

-
+
type t
diff --git a/test/generators/html/Ocamlary-With9.html b/test/generators/html/Ocamlary-With9.html index d4ff16d40a..db565972dd 100644 --- a/test/generators/html/Ocamlary-With9.html +++ b/test/generators/html/Ocamlary-With9.html @@ -16,7 +16,7 @@

Module Ocamlary.With9

-
+
module diff --git a/test/generators/html/Ocamlary-class-one_method_class.html b/test/generators/html/Ocamlary-class-one_method_class.html index 4214c8f8b4..f996b21685 100644 --- a/test/generators/html/Ocamlary-class-one_method_class.html +++ b/test/generators/html/Ocamlary-class-one_method_class.html @@ -16,7 +16,7 @@

Class Ocamlary.one_method_class

-
+
method go : unit
diff --git a/test/generators/html/Ocamlary-class-param_class.html b/test/generators/html/Ocamlary-class-param_class.html index 91b86c8965..551bfb2ca0 100644 --- a/test/generators/html/Ocamlary-class-param_class.html +++ b/test/generators/html/Ocamlary-class-param_class.html @@ -16,7 +16,7 @@

Class Ocamlary.param_class

-
+
method v : diff --git a/test/generators/html/Ocamlary-class-two_method_class.html b/test/generators/html/Ocamlary-class-two_method_class.html index 18ab67f12c..d8cab62460 100644 --- a/test/generators/html/Ocamlary-class-two_method_class.html +++ b/test/generators/html/Ocamlary-class-two_method_class.html @@ -16,7 +16,7 @@

Class Ocamlary.two_method_class

-
+
method one : @@ -26,7 +26,7 @@

Class Ocamlary.two_method_class

-
+
method undo : unit diff --git a/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html index c502d8f452..ee03c1c085 100644 --- a/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html @@ -22,7 +22,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html index a88eb59ee4..48f6b994ba 100644 --- a/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -23,7 +23,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA.html b/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA.html index 777d7b2c2c..0821f72d9a 100644 --- a/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA.html +++ b/test/generators/html/Ocamlary-module-type-A-Q-InnerModuleA.html @@ -19,7 +19,7 @@

Module Q.InnerModuleA

-
+
type t = @@ -30,7 +30,7 @@

Module Q.InnerModuleA

This comment is for t.

-
+
module @@ -48,8 +48,7 @@

Module Q.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-A-Q.html b/test/generators/html/Ocamlary-module-type-A-Q.html index 075620c0f0..68a808fcfd 100644 --- a/test/generators/html/Ocamlary-module-type-A-Q.html +++ b/test/generators/html/Ocamlary-module-type-A-Q.html @@ -17,7 +17,7 @@

This comment is for CollectionModule.

-
+
type collection
@@ -25,13 +25,13 @@
-
+
type element
-
+
module @@ -47,8 +47,7 @@
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-A.html b/test/generators/html/Ocamlary-module-type-A.html index 0a9ca17673..e8add19438 100644 --- a/test/generators/html/Ocamlary-module-type-A.html +++ b/test/generators/html/Ocamlary-module-type-A.html @@ -15,13 +15,13 @@

Module type Ocamlary.A

-
+
type t
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html index cf50edc2be..3faf8e4ab9 100644 --- a/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html @@ -22,7 +22,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html index 16480eb4d9..f80e27e4dc 100644 --- a/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -23,7 +23,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA.html b/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA.html index 7b4503145c..551fa20f19 100644 --- a/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA.html +++ b/test/generators/html/Ocamlary-module-type-B-Q-InnerModuleA.html @@ -19,7 +19,7 @@

Module Q.InnerModuleA

-
+
type t = @@ -30,7 +30,7 @@

Module Q.InnerModuleA

This comment is for t.

-
+
module @@ -48,8 +48,7 @@

Module Q.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-B-Q.html b/test/generators/html/Ocamlary-module-type-B-Q.html index 4af918690a..ef94836b6f 100644 --- a/test/generators/html/Ocamlary-module-type-B-Q.html +++ b/test/generators/html/Ocamlary-module-type-B-Q.html @@ -17,7 +17,7 @@

This comment is for CollectionModule.

-
+
type collection
@@ -25,13 +25,13 @@
-
+
type element
-
+
module @@ -47,8 +47,7 @@
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-B.html b/test/generators/html/Ocamlary-module-type-B.html index 782d07bf7e..62aa0087ba 100644 --- a/test/generators/html/Ocamlary-module-type-B.html +++ b/test/generators/html/Ocamlary-module-type-B.html @@ -15,13 +15,13 @@

Module type Ocamlary.B

-
+
type t
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html index 9a9d83e5d1..6b1e6c4198 100644 --- a/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html @@ -22,7 +22,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html index a2decc7d2a..6550ed03db 100644 --- a/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -23,7 +23,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA.html b/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA.html index a30f152b5b..83d8a3e4f9 100644 --- a/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA.html +++ b/test/generators/html/Ocamlary-module-type-C-Q-InnerModuleA.html @@ -19,7 +19,7 @@

Module Q.InnerModuleA

-
+
type t = @@ -30,7 +30,7 @@

Module Q.InnerModuleA

This comment is for t.

-
+
module @@ -48,8 +48,7 @@

Module Q.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-C-Q.html b/test/generators/html/Ocamlary-module-type-C-Q.html index f65e8ccbbc..e3410d1acd 100644 --- a/test/generators/html/Ocamlary-module-type-C-Q.html +++ b/test/generators/html/Ocamlary-module-type-C-Q.html @@ -17,7 +17,7 @@

This comment is for CollectionModule.

-
+
type collection
@@ -25,13 +25,13 @@
-
+
type element
-
+
module @@ -47,8 +47,7 @@
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-C.html b/test/generators/html/Ocamlary-module-type-C.html index 4f7650190b..1947d91bee 100644 --- a/test/generators/html/Ocamlary-module-type-C.html +++ b/test/generators/html/Ocamlary-module-type-C.html @@ -32,13 +32,13 @@

Module type Ocamlary.C

-
+
type t
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html index ff7ad9a015..c1d3d0ed89 100644 --- a/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html @@ -23,7 +23,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html index 2860843ffb..49f0c9c3ac 100644 --- a/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -24,7 +24,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA.html b/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA.html index 0312fc4534..a72e90463a 100644 --- a/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA.html +++ b/test/generators/html/Ocamlary-module-type-COLLECTION-InnerModuleA.html @@ -19,7 +19,7 @@

Module COLLECTION.InnerModuleA

-
+
type t = @@ -32,7 +32,7 @@

Module COLLECTION.InnerModuleA

This comment is for t.

-
+
module @@ -51,8 +51,7 @@

Module COLLECTION.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-COLLECTION.html b/test/generators/html/Ocamlary-module-type-COLLECTION.html index 0e37510ec8..198eb89712 100644 --- a/test/generators/html/Ocamlary-module-type-COLLECTION.html +++ b/test/generators/html/Ocamlary-module-type-COLLECTION.html @@ -18,7 +18,7 @@

Module type Ocamlary.COLLECTION

This comment is for CollectionModule.

-
+
type collection
@@ -26,13 +26,13 @@

Module type Ocamlary.COLLECTION

-
+
type element
-
+
module @@ -50,8 +50,7 @@

Module type Ocamlary.COLLECTION

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-Dep10.html b/test/generators/html/Ocamlary-module-type-Dep10.html index 282f062a40..57e690f925 100644 --- a/test/generators/html/Ocamlary-module-type-Dep10.html +++ b/test/generators/html/Ocamlary-module-type-Dep10.html @@ -16,7 +16,7 @@

Module type Ocamlary.Dep10

-
+
type t = int diff --git a/test/generators/html/Ocamlary-module-type-Empty.html b/test/generators/html/Ocamlary-module-type-Empty.html index a2d80b399d..4e9c7f2c56 100644 --- a/test/generators/html/Ocamlary-module-type-Empty.html +++ b/test/generators/html/Ocamlary-module-type-Empty.html @@ -17,7 +17,7 @@

Module type Ocamlary.Empty

-
+
type t
diff --git a/test/generators/html/Ocamlary-module-type-IncludeInclude2.html b/test/generators/html/Ocamlary-module-type-IncludeInclude2.html index a32ddd6a6f..e3a0286d07 100644 --- a/test/generators/html/Ocamlary-module-type-IncludeInclude2.html +++ b/test/generators/html/Ocamlary-module-type-IncludeInclude2.html @@ -16,7 +16,7 @@

Module type Ocamlary.IncludeInclude2

-
+
type include_include diff --git a/test/generators/html/Ocamlary-module-type-IncludedB.html b/test/generators/html/Ocamlary-module-type-IncludedB.html index 400f8ca175..de09d5e9fa 100644 --- a/test/generators/html/Ocamlary-module-type-IncludedB.html +++ b/test/generators/html/Ocamlary-module-type-IncludedB.html @@ -16,7 +16,7 @@

Module type Ocamlary.IncludedB

-
+
type s
diff --git a/test/generators/html/Ocamlary-module-type-M.html b/test/generators/html/Ocamlary-module-type-M.html index 62cb897745..7c9f8c507b 100644 --- a/test/generators/html/Ocamlary-module-type-M.html +++ b/test/generators/html/Ocamlary-module-type-M.html @@ -15,7 +15,7 @@

Module type Ocamlary.M

-
+
type t
diff --git a/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html index 492d5d20b2..c27f140d85 100644 --- a/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html @@ -23,7 +23,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html index 6b4610dc48..d635c1b0be 100644 --- a/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -23,7 +23,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA.html b/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA.html index a95a360d20..cfffc8e88b 100644 --- a/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA.html +++ b/test/generators/html/Ocamlary-module-type-MMM-C-InnerModuleA.html @@ -19,7 +19,7 @@

Module C.InnerModuleA

-
+
type t = @@ -31,7 +31,7 @@

Module C.InnerModuleA

This comment is for t.

-
+
module @@ -49,8 +49,7 @@

Module C.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-MMM-C.html b/test/generators/html/Ocamlary-module-type-MMM-C.html index a134924f81..31454cc388 100644 --- a/test/generators/html/Ocamlary-module-type-MMM-C.html +++ b/test/generators/html/Ocamlary-module-type-MMM-C.html @@ -18,7 +18,7 @@

Module MMM.C

This comment is for CollectionModule.

-
+
type collection
@@ -26,13 +26,13 @@

Module MMM.C

-
+
type element
-
+
module @@ -49,8 +49,7 @@

Module MMM.C

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-MMM.html b/test/generators/html/Ocamlary-module-type-MMM.html index eaa810953f..0c458bfe04 100644 --- a/test/generators/html/Ocamlary-module-type-MMM.html +++ b/test/generators/html/Ocamlary-module-type-MMM.html @@ -16,7 +16,7 @@

Module type Ocamlary.MMM

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-MissingComment.html b/test/generators/html/Ocamlary-module-type-MissingComment.html index b4a1287d96..d9060a6a4d 100644 --- a/test/generators/html/Ocamlary-module-type-MissingComment.html +++ b/test/generators/html/Ocamlary-module-type-MissingComment.html @@ -17,7 +17,7 @@

Module type Ocamlary.MissingComment

-
+
type t
diff --git a/test/generators/html/Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html b/test/generators/html/Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html index e8921328ad..28b8e8deb6 100644 --- a/test/generators/html/Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html +++ b/test/generators/html/Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html @@ -20,7 +20,7 @@

Module type NestedInclude1.NestedInclude2
-
+
type nested_include diff --git a/test/generators/html/Ocamlary-module-type-NestedInclude1.html b/test/generators/html/Ocamlary-module-type-NestedInclude1.html index a4c32fed88..2eaf49f39a 100644 --- a/test/generators/html/Ocamlary-module-type-NestedInclude1.html +++ b/test/generators/html/Ocamlary-module-type-NestedInclude1.html @@ -16,8 +16,7 @@

Module type Ocamlary.NestedInclude1

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-NestedInclude2.html b/test/generators/html/Ocamlary-module-type-NestedInclude2.html index 622ea7c091..6fa4d76709 100644 --- a/test/generators/html/Ocamlary-module-type-NestedInclude2.html +++ b/test/generators/html/Ocamlary-module-type-NestedInclude2.html @@ -16,7 +16,7 @@

Module type Ocamlary.NestedInclude2

-
+
type nested_include diff --git a/test/generators/html/Ocamlary-module-type-RECOLLECTION.html b/test/generators/html/Ocamlary-module-type-RECOLLECTION.html index e52212b42b..e2961953e2 100644 --- a/test/generators/html/Ocamlary-module-type-RECOLLECTION.html +++ b/test/generators/html/Ocamlary-module-type-RECOLLECTION.html @@ -16,7 +16,7 @@

Module type Ocamlary.RECOLLECTION

-
+
module C = diff --git a/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html b/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html index acebd23bb4..b566895df5 100644 --- a/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html +++ b/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html @@ -25,7 +25,7 @@

Module InnerModuleA.InnerModuleA'

-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html b/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html index e5ba1ec48d..f24414a7bb 100644 --- a/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html +++ b/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html @@ -26,7 +26,7 @@

Module type InnerModuleA.InnerModuleTypeA'
-
+
type t = diff --git a/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA.html b/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA.html index 50bf7edae9..1b87b62c9c 100644 --- a/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA.html +++ b/test/generators/html/Ocamlary-module-type-RecollectionModule-InnerModuleA.html @@ -20,7 +20,7 @@

Module RecollectionModule.InnerModuleA

-
+
type t = @@ -33,7 +33,7 @@

Module RecollectionModule.InnerModuleA

This comment is for t.

-
+
module @@ -52,8 +52,7 @@

Module RecollectionModule.InnerModuleA

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-RecollectionModule.html b/test/generators/html/Ocamlary-module-type-RecollectionModule.html index 5f52c18323..1ea17107e7 100644 --- a/test/generators/html/Ocamlary-module-type-RecollectionModule.html +++ b/test/generators/html/Ocamlary-module-type-RecollectionModule.html @@ -16,7 +16,7 @@

Module type Ocamlary.RecollectionModule

-
+
type collection = @@ -30,7 +30,7 @@

Module type Ocamlary.RecollectionModule

-
+
type element = @@ -42,7 +42,7 @@

Module type Ocamlary.RecollectionModule

-
+
module @@ -60,8 +60,7 @@

Module type Ocamlary.RecollectionModule

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-SigForMod-Inner.html b/test/generators/html/Ocamlary-module-type-SigForMod-Inner.html index 217bdea041..89969215fa 100644 --- a/test/generators/html/Ocamlary-module-type-SigForMod-Inner.html +++ b/test/generators/html/Ocamlary-module-type-SigForMod-Inner.html @@ -18,7 +18,7 @@

Module SigForMod.Inner

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-SigForMod.html b/test/generators/html/Ocamlary-module-type-SigForMod.html index 1ca3c4a8b1..6f50cc1a82 100644 --- a/test/generators/html/Ocamlary-module-type-SigForMod.html +++ b/test/generators/html/Ocamlary-module-type-SigForMod.html @@ -17,7 +17,7 @@

Module type Ocamlary.SigForMod

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-EmptySig.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-EmptySig.html index d0c5519238..39654f5504 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-EmptySig.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-EmptySig.html @@ -18,7 +18,7 @@

Module type SuperSig.EmptySig

-
+
type not_actually_empty diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-One.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-One.html index 96b3f4ca59..b9ece0a14f 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-One.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-One.html @@ -18,7 +18,7 @@

Module type SuperSig.One

-
+
type two
diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html index 4d3c729844..97b4941b73 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html @@ -21,7 +21,7 @@

Module SubSigA.SubSigAMod

-
+
type sub_sig_a_mod diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html index ef9c353895..d24bbdc449 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html @@ -27,13 +27,13 @@

A Labeled Section Header Inside of a Signature

-
+
type t
-
+
module diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html index ceb73b4ae3..8b62e03439 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html @@ -29,7 +29,7 @@

Another Labeled Section Header Inside of a Signature

-
+
type t
diff --git a/test/generators/html/Ocamlary-module-type-SuperSig.html b/test/generators/html/Ocamlary-module-type-SuperSig.html index 82f752bc58..eae4228e14 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig.html @@ -16,7 +16,7 @@

Module type Ocamlary.SuperSig

-
+
module @@ -32,7 +32,7 @@

Module type Ocamlary.SuperSig

-
+
module @@ -48,7 +48,7 @@

Module type Ocamlary.SuperSig

-
+
module @@ -64,7 +64,7 @@

Module type Ocamlary.SuperSig

-
+
module @@ -78,7 +78,7 @@

Module type Ocamlary.SuperSig

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-ToInclude-IncludedA.html b/test/generators/html/Ocamlary-module-type-ToInclude-IncludedA.html index 7cbc560d74..ac63fe3bcd 100644 --- a/test/generators/html/Ocamlary-module-type-ToInclude-IncludedA.html +++ b/test/generators/html/Ocamlary-module-type-ToInclude-IncludedA.html @@ -18,7 +18,7 @@

Module ToInclude.IncludedA

-
+
type t
diff --git a/test/generators/html/Ocamlary-module-type-ToInclude-module-type-IncludedB.html b/test/generators/html/Ocamlary-module-type-ToInclude-module-type-IncludedB.html index a6db5d8fa8..ef6d2b6ddf 100644 --- a/test/generators/html/Ocamlary-module-type-ToInclude-module-type-IncludedB.html +++ b/test/generators/html/Ocamlary-module-type-ToInclude-module-type-IncludedB.html @@ -18,7 +18,7 @@

Module type ToInclude.IncludedB

-
+
type s
diff --git a/test/generators/html/Ocamlary-module-type-ToInclude.html b/test/generators/html/Ocamlary-module-type-ToInclude.html index e0a96de239..415db1da06 100644 --- a/test/generators/html/Ocamlary-module-type-ToInclude.html +++ b/test/generators/html/Ocamlary-module-type-ToInclude.html @@ -16,7 +16,7 @@

Module type Ocamlary.ToInclude

-
+
module @@ -29,7 +29,7 @@

Module type Ocamlary.ToInclude

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-TypeExt.html b/test/generators/html/Ocamlary-module-type-TypeExt.html index 393ca7108c..39c2d909a0 100644 --- a/test/generators/html/Ocamlary-module-type-TypeExt.html +++ b/test/generators/html/Ocamlary-module-type-TypeExt.html @@ -16,7 +16,7 @@

Module type Ocamlary.TypeExt

-
+
type t = .. @@ -24,24 +24,23 @@

Module type Ocamlary.TypeExt

-
+
type t += - - - - -
- | C - -
+
    +
  1. + + | C + +
  2. +
-
+
val f : diff --git a/test/generators/html/Ocamlary-module-type-TypeExtPruned.html b/test/generators/html/Ocamlary-module-type-TypeExtPruned.html index bba8234828..6ac4312d42 100644 --- a/test/generators/html/Ocamlary-module-type-TypeExtPruned.html +++ b/test/generators/html/Ocamlary-module-type-TypeExtPruned.html @@ -16,25 +16,24 @@

Module type Ocamlary.TypeExtPruned

-
+
type new_t += - - - - -
- | C - -
+
    +
  1. + + | C + +
  2. +
-
+
val f : diff --git a/test/generators/html/Ocamlary-module-type-With1-M.html b/test/generators/html/Ocamlary-module-type-With1-M.html index d0a263fc61..ab4ebf89d0 100644 --- a/test/generators/html/Ocamlary-module-type-With1-M.html +++ b/test/generators/html/Ocamlary-module-type-With1-M.html @@ -17,7 +17,7 @@

Module With1.M

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-With1.html b/test/generators/html/Ocamlary-module-type-With1.html index bd56b0aff9..ae5d801aad 100644 --- a/test/generators/html/Ocamlary-module-type-With1.html +++ b/test/generators/html/Ocamlary-module-type-With1.html @@ -16,7 +16,7 @@

Module type Ocamlary.With1

-
+
module @@ -29,7 +29,7 @@

Module type Ocamlary.With1

-
+
module N : diff --git a/test/generators/html/Ocamlary-module-type-With11-N.html b/test/generators/html/Ocamlary-module-type-With11-N.html index a92bba9e17..a339813df3 100644 --- a/test/generators/html/Ocamlary-module-type-With11-N.html +++ b/test/generators/html/Ocamlary-module-type-With11-N.html @@ -17,7 +17,7 @@

Module With11.N

-
+
type t = int diff --git a/test/generators/html/Ocamlary-module-type-With11.html b/test/generators/html/Ocamlary-module-type-With11.html index db4f75c94f..880f0b1de3 100644 --- a/test/generators/html/Ocamlary-module-type-With11.html +++ b/test/generators/html/Ocamlary-module-type-With11.html @@ -16,7 +16,7 @@

Module type Ocamlary.With11

-
+
module M = With9 @@ -24,7 +24,7 @@

Module type Ocamlary.With11

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-With8-M-N.html b/test/generators/html/Ocamlary-module-type-With8-M-N.html index a1004aed0f..92ea6e5ba1 100644 --- a/test/generators/html/Ocamlary-module-type-With8-M-N.html +++ b/test/generators/html/Ocamlary-module-type-With8-M-N.html @@ -17,7 +17,7 @@
-
+
type t = With5.N.t diff --git a/test/generators/html/Ocamlary-module-type-With8-M.html b/test/generators/html/Ocamlary-module-type-With8-M.html index 84b89fdb0f..179509281d 100644 --- a/test/generators/html/Ocamlary-module-type-With8-M.html +++ b/test/generators/html/Ocamlary-module-type-With8-M.html @@ -17,7 +17,7 @@

Module With8.M

-
+
module @@ -28,7 +28,7 @@

Module With8.M

-
+
module diff --git a/test/generators/html/Ocamlary-module-type-With8.html b/test/generators/html/Ocamlary-module-type-With8.html index 681ac51ccf..cad25f567d 100644 --- a/test/generators/html/Ocamlary-module-type-With8.html +++ b/test/generators/html/Ocamlary-module-type-With8.html @@ -16,7 +16,7 @@

Module type Ocamlary.With8

-
+
module diff --git a/test/generators/html/Ocamlary.html b/test/generators/html/Ocamlary.html index 5d8fdcf36f..a77e59142c 100644 --- a/test/generators/html/Ocamlary.html +++ b/test/generators/html/Ocamlary.html @@ -99,7 +99,7 @@

Basic module stuff

-
+
module @@ -112,7 +112,7 @@

A plain, empty module

-
+
module @@ -127,8 +127,7 @@

An ambiguous, misnamed module type

-
+
module @@ -143,7 +142,7 @@

An ambiguous, misnamed module type

Section 9000

-
+
module EmptyAlias = Empty @@ -154,7 +153,7 @@

EmptySig

-
+
module @@ -168,8 +167,7 @@

EmptySig

A plain, empty module signature

-
+
module @@ -183,7 +181,7 @@

EmptySig

-
+
module @@ -201,8 +199,7 @@

EmptySig

-
+
module @@ -217,7 +214,7 @@

EmptySig

A plain module with an alias signature

-
+
module @@ -230,7 +227,7 @@

EmptySig

-
+
module @@ -247,7 +244,7 @@

EmptySig

-
+
module @@ -275,7 +272,7 @@

EmptySig

is the module signature.

-
+
module @@ -297,7 +294,7 @@

stuff

After exception title.

-
+
exception Kaboom @@ -307,7 +304,7 @@

Unary exception constructor

-
+
exception Kablam @@ -317,7 +314,7 @@

Binary exception constructor

-
+
exception Kapow @@ -330,7 +327,7 @@

-
+
exception EmptySig @@ -346,7 +343,7 @@

-
+
exception EmptySigAlias @@ -364,7 +361,7 @@

Basic type and value stuff with advanced doc comments

-
+
type @@ -385,7 +382,7 @@

-
+
val a_function : @@ -408,7 +405,7 @@

-
+
val fun_fun_fun : @@ -427,7 +424,7 @@

-
+
val fun_maybe : @@ -438,7 +435,7 @@

-
+
val not_found : @@ -455,7 +452,7 @@

-
+
val ocaml_org : string @@ -470,7 +467,7 @@

-
+
val some_file : string @@ -485,7 +482,7 @@

-
+
val some_doc : string @@ -500,7 +497,7 @@

-
+
val since_mesozoic : unit @@ -514,7 +511,7 @@

-
+
val changing : unit @@ -540,86 +537,86 @@

Some Operators

-
+
val (~-) : unit
-
+
val (!) : unit
-
+
val (@) : unit
-
+
val ($) : unit
-
+
val (%) : unit
-
+
val (&) : unit
-
+
val (*) : unit
-
+
val (-) : unit
-
+
val (+) : unit
-
+
val (-?) : unit
-
+
val (/) : unit
-
+
val (:=) : unit
-
+
val (=) : unit
-
+
val (land) : unit
@@ -629,7 +626,7 @@

Stuff

-
+
module @@ -645,8 +642,8 @@

-
+
+ module type @@ -660,7 +657,7 @@

module type of

-
+
module @@ -699,7 +696,7 @@

-
+
module @@ -713,8 +710,8 @@

-
+
+ module type @@ -732,8 +729,8 @@

-
+
module @@ -749,7 +746,7 @@

-
+
module @@ -763,7 +760,7 @@

-
+
module @@ -777,7 +774,7 @@

-
+
module @@ -793,7 +790,7 @@

-
+
module @@ -817,8 +814,7 @@

-
+
module @@ -837,7 +833,7 @@

-
+
module @@ -860,7 +856,7 @@

-
+
module @@ -873,8 +869,8 @@

-
+
+ module type @@ -892,191 +888,166 @@

Advanced Type Stuff

-
+
type record = { - - - - - - - - - -
- - field1 : int; - (* +
    +
  1. + + field1 : int; +
    (*

    This comment is for field1.

    *) -
- - field2 : int; - (* + + +
  • + + field2 : int; +
    (*

    This comment is for field2.

    *) -
  • } +
    + + }

    This comment is for record.

    This comment is also for record.

    -
    +
    type mutable_record = { - - - - - - - - - - - - - -
    - - mutable a : int; - - (* +
      +
    1. + + mutable a : int; + +
      (*

      a is first and mutable

      *) -
    - - b : unit; - (* + + +
  • + + b : unit; +
    (*

    b is second and immutable

    *) -
  • - - mutable c : int; - - (* + + +
  • + + mutable c : int; + +
    (*

    c is third and mutable

    *) -
  • } +
    + + }
    -
    +
    type universe_record = { - - - - -
    - - - nihilate : 'a. - 'a - -> - unit; - - -
    } +
      +
    1. + + nihilate : 'a. + 'a + -> + unit; + + +
    2. +
    }
    -
    +
    type variant = - - - - - - - - - - - - - - - - - -
    - - | - TagA - - (* +
      +
    1. + + | + TagA + +
      (*

      This comment is for TagA.

      *) -
    - - | - ConstrB - of int - - - (* + + +
  • + + | + ConstrB + of int + + +
    (*

    This comment is for ConstrB.

    *) -
  • - - | - ConstrC - of int * int - - - (* + + +
  • + + | + ConstrC + of int * int + + +
    (*

    This comment is for binary ConstrC.

    *) -
  • - - | - ConstrD - of int * int - - - (* + + +
  • + + | + 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 - -
    ] +
      +
    1. + + | `TagA +
    2. +
    3. + + | + `ConstrB of int +
    4. +
    ]

    This comment is for poly_variant.

    @@ -1084,124 +1055,111 @@

    -
    +
    type (_, _) full_gadt = - - - - - - - - - - - - - -
    - - | - Tag : - (unit, unit) - full_gadt - +
      +
    1. + + | + Tag : + (unit, unit) + full_gadt - -
    - - | - First : - 'a - -> - ('a, unit) - full_gadt - + + + +
  • + + | + First : + 'a + -> + ('a, unit) + full_gadt - -
  • - - | - Second : - 'a - -> - (unit, 'a) - full_gadt - + + + +
  • + + | + Second : + 'a + -> + (unit, 'a) + full_gadt - -
  • - - | - Exist : - 'a * 'b - -> - ('b, unit) - 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 - +
      +
    1. + | + AscribeTag : + 'a + partial_gadt - -
    - - | - OfTag - of - 'a - partial_gadt - + + + +
  • + | + OfTag + of + 'a + partial_gadt - -
  • - - | - ExistGadtTag : - ( - 'a - -> - 'b) - -> + + + +
  • + + | + ExistGadtTag : + ( 'a - partial_gadt - + -> + 'b) + -> + 'a + partial_gadt - -
  • + + + +

    This comment is for partial_gadt.

    @@ -1209,7 +1167,7 @@

    -
    +
    type alias = variant @@ -1219,7 +1177,7 @@

    -
    +
    type tuple = @@ -1236,168 +1194,148 @@

    -
    +
    type variant_alias = variant = - - - - - - - - - - - - - -
    - - | - TagA - -
    - - | - ConstrB - of int - - -
    - - | - ConstrC - of int * int - - -
    - - | - ConstrD - of int * int - - -
    +
      +
    1. + | + TagA + +
    2. +
    3. + | + ConstrB + of int + + +
    4. +
    5. + | + ConstrC + of int * int + + +
    6. +
    7. + | + ConstrD + of int * int + + +
    8. +

    This comment is for variant_alias.

    -
    +
    type record_alias = record = { - - - - - - - -
    - - field1 : int; -
    - - field2 : int; -
    } +
      +
    1. + + field1 : int; +
    2. +
    3. + + field2 : int; +
    4. +
    }

    This comment is for record_alias.

    -
    +
    type poly_variant_union = [ - - - - - - - -
    - - | - poly_variant - -
    - - | `TagC -
    ] +
      +
    1. + + | + poly_variant + +
    2. +
    3. + + | `TagC +
    4. +
    ]

    This comment is for poly_variant_union.

    -
    +
    type 'a poly_poly_variant = [ - - - - -
    - - | - - `TagA of - 'a - - -
    ] +
      +
    1. + + | + + `TagA of + 'a + + +
    2. +
    ]
    -
    +
    type ('a, 'b) bin_poly_poly_variant = [ - - - - - - - -
    - - | - - `TagA of - 'a - - -
    - - | - - `ConstrB of - 'b - - -
    ] +
      +
    1. + + | + + `TagA of + 'a + + +
    2. +
    3. + + | + + `ConstrB of + 'b + + +
    4. +
    ]
    -
    +
    type @@ -1409,7 +1347,7 @@

    -
    +
    type @@ -1422,7 +1360,7 @@

    -
    +
    type @@ -1439,7 +1377,7 @@

    -
    +
    type 'a poly_fun @@ -1453,7 +1391,7 @@

    -
    +
    type @@ -1471,7 +1409,7 @@

    -
    +
    type @@ -1484,7 +1422,7 @@

    -
    +
    type @@ -1499,51 +1437,43 @@

    -
    +
    type nested_poly_variant = [ - - - - - - - - - - - - - -
    - - | `A -
    - - | - - `B of - [ `B1 | `B2 ] - - -
    - - | `C -
    - - | - - `D of - [ `D1 of [ `D1a ] ] - - -
    ] +
      +
    1. + + | `A +
    2. +
    3. + + | + + `B of + [ `B1 | `B2 ] + + +
    4. +
    5. + + | `C +
    6. +
    7. + + | + + `D of + [ `D1 of [ `D1a ] ] + + +
    8. +
    ]
    -
    +
    type @@ -1557,69 +1487,61 @@

    = - - - - - - - - - - - - - -
    - - | - Tag : - (unit, unit) - full_gadt_alias - +
      +
    1. + | + Tag : + (unit, unit) + full_gadt_alias - -
    - - | - First : - 'a - -> - ('a, unit) - full_gadt_alias - + + + +
  • + | + First : + 'a + -> + ('a, unit) + full_gadt_alias - -
  • - - | - Second : - 'a - -> - (unit, 'a) - full_gadt_alias - + + + +
  • + | + Second : + 'a + -> + (unit, 'a) + full_gadt_alias - -
  • - - | - Exist : - 'a * 'b - -> - ('b, unit) - full_gadt_alias - + + + +
  • + | + Exist : + 'a * 'b + -> + ('b, unit) + full_gadt_alias - -
  • + +
    + +

    This comment is for full_gadt_alias.

    -
    +
    type @@ -1631,57 +1553,53 @@

    = - - - - - - - - - - -
    - - | - AscribeTag : - 'a - partial_gadt_alias - +
      +
    1. + + | + AscribeTag : + 'a + partial_gadt_alias - -
    - - | - OfTag - of - 'a - partial_gadt_alias - + + + +
  • + | + OfTag + of + 'a + partial_gadt_alias - -
  • - - | - ExistGadtTag : - ( - 'a - -> - 'b) - -> + + + +
  • + + | + ExistGadtTag : + ( 'a - partial_gadt_alias - + -> + 'b) + -> + 'a + partial_gadt_alias - -
  • + +
    + +

    This comment is for partial_gadt_alias.

    -
    +
    exception Exn_arrow : unit @@ -1696,39 +1614,35 @@

    -
    +
    type mutual_constr_a = - - - - - - - - -
    - - | A - -
    - - | - B_ish - of - mutual_constr_b - - - (* +
      +
    1. + | A + +
    2. +
    3. + | + B_ish + of + mutual_constr_b + + +
      (*

      This comment is between mutual_constr_a and mutual_constr_b .

      *) -
    +
    + +

    This comment is for @@ -1739,35 +1653,31 @@

    -
    +
    and mutual_constr_b = - - - - - - - - -
    - - | B - -
    - - | - A_ish - of - mutual_constr_a - - - (* +
      +
    1. + | B + +
    2. +
    3. + | + A_ish + of + mutual_constr_a + + +
      (*

      This comment must be here for the next to associate correctly.

      *) -
    +
    + +

    This comment is for @@ -1778,7 +1688,7 @@

    -
    +
    type rec_obj = @@ -1791,7 +1701,7 @@

    -
    +
    type 'a open_obj @@ -1804,7 +1714,7 @@

    -
    +
    type 'a oof = @@ -1817,7 +1727,7 @@

    -
    +
    type 'a any_obj @@ -1827,7 +1737,7 @@

    -
    +
    type empty_obj = < > @@ -1835,7 +1745,7 @@

    -
    +
    type one_meth = < meth : unit > @@ -1843,7 +1753,7 @@

    -
    +
    type ext = .. @@ -1851,110 +1761,98 @@

    A mystery wrapped in an ellipsis

    -
    +
    + type ext += - - - - -
    - - | ExtA - -
    +
      +
    1. + + | ExtA + +
    2. +
    -
    +
    + type ext += - - - - -
    - - | ExtB - -
    +
      +
    1. + + | ExtB + +
    2. +
    -
    +
    + type ext += - - - - - - - -
    - - | - ExtC - of unit - - -
    - - | - ExtD - of ext - - -
    +
      +
    1. + + | + ExtC + of unit + + +
    2. +
    3. + + | + ExtD + of ext + + +
    4. +
    -
    +
    + type ext += - - - - -
    - - | ExtE - -
    +
      +
    1. + + | ExtE + +
    2. +
    -
    +
    + type ext += - - - - -
    - - | ExtF - -
    +
      +
    1. + + | ExtF + +
    2. +
    -
    +
    type 'a poly_ext @@ -1963,66 +1861,62 @@

    'a poly_ext

    -
    +
    type poly_ext += - - - - - - - - -
    - | - Foo - of 'b - - -
    - | - Bar - of 'b - * 'b - - - (* +
      +
    1. + + | + Foo + of 'b + + +
    2. +
    3. + + | + Bar + of 'b + * 'b + + +
      (*

      'b poly_ext

      *) -
    +
    + +
    -
    +
    + type poly_ext += - - - - - -
    - - | - Quux - of 'c - - - (* +
      +
    1. + + | + Quux + of 'c + + +
      (*

      'c poly_ext

      *) -
    +
    + +
    -
    +
    module @@ -2035,56 +1929,52 @@

    -
    +
    + type ExtMod.t += - - - - - -
    - - | - ZzzTop0 - - (* +
      +
    1. + + | + ZzzTop0 + +
      (*

      It's got the rock

      *) -
    +
    + +
    -
    +
    + type ExtMod.t += - - - - - -
    - - | - ZzzTop - of unit - - - (* +
      +
    1. + + | + ZzzTop + of unit + + +
      (*

      and it packs a unit.

      *) -
    +
    + +
    -
    +
    + val launch_missiles : unit -> unit @@ -2093,7 +1983,7 @@

    Rotate keys on my mark...

    -
    +
    type my_mod = @@ -2108,7 +1998,7 @@

    -
    +
    class empty_class @@ -2119,7 +2009,7 @@

    -
    +
    class @@ -2132,7 +2022,7 @@

    -
    +
    class @@ -2145,7 +2035,7 @@

    -
    +
    class 'a param_class @@ -2159,7 +2049,7 @@

    -
    +
    type my_unit_object = @@ -2170,7 +2060,7 @@

    -
    +
    type 'a my_unit_class @@ -2183,7 +2073,7 @@

    -
    +
    module @@ -2196,7 +2086,7 @@

    -
    +
    module @@ -2211,7 +2101,7 @@

    -
    +
    type dep1 = @@ -2221,7 +2111,7 @@

    -
    +
    module @@ -2234,7 +2124,7 @@

    -
    +
    module @@ -2247,7 +2137,7 @@

    -
    +
    module @@ -2262,7 +2152,7 @@

    -
    +
    type dep2 = @@ -2272,7 +2162,7 @@

    -
    +
    type dep3 = Dep5(Dep4).Z.Y.a @@ -2281,7 +2171,7 @@

    -
    +
    module @@ -2294,7 +2184,7 @@

    -
    +
    module @@ -2309,7 +2199,7 @@

    -
    +
    type dep4 = @@ -2320,7 +2210,7 @@

    -
    +
    module @@ -2333,7 +2223,7 @@

    -
    +
    module @@ -2348,7 +2238,7 @@

    -
    +
    module @@ -2365,7 +2255,7 @@

    -
    +
    module @@ -2378,7 +2268,7 @@

    -
    +
    module @@ -2393,7 +2283,7 @@

    -
    +
    module @@ -2405,7 +2295,7 @@

    -
    +
    type dep5 = Dep13.c @@ -2413,7 +2303,7 @@

    -
    +
    module @@ -2427,7 +2317,7 @@

    -
    +
    module @@ -2440,7 +2330,7 @@

    -
    +
    module @@ -2457,7 +2347,7 @@

    -
    +
    type with1 = With3.N.t @@ -2465,7 +2355,7 @@

    -
    +
    module @@ -2482,7 +2372,7 @@

    -
    +
    type with2 = With4.N.t @@ -2490,7 +2380,7 @@

    -
    +
    module @@ -2503,7 +2393,7 @@

    -
    +
    module @@ -2516,7 +2406,7 @@

    -
    +
    module @@ -2531,7 +2421,7 @@

    -
    +
    module @@ -2555,7 +2445,7 @@

    -
    +
    module @@ -2568,7 +2458,7 @@

    -
    +
    module @@ -2581,7 +2471,7 @@

    -
    +
    module @@ -2604,8 +2494,7 @@

    -
    +
    module @@ -2628,8 +2517,7 @@

    -
    +
    module @@ -2662,7 +2550,7 @@

    -
    +
    type nested_include = int @@ -2672,7 +2560,7 @@

    -
    +
    module @@ -2685,7 +2573,7 @@

    -
    +
    module @@ -2711,7 +2599,7 @@

    -
    +
    type double_include @@ -2720,7 +2608,7 @@

    -
    +
    module @@ -2744,8 +2632,7 @@

    -
    +
    module @@ -2760,7 +2647,7 @@

    -
    +
    module @@ -2785,7 +2672,7 @@

    -
    +
    type include_include @@ -2832,7 +2719,7 @@

    with @canonical paths

    -
    +
    module @@ -2860,7 +2747,7 @@

    Aliases again

    -
    +
    module @@ -2910,7 +2797,7 @@

    syntax

    -
    +
    module @@ -2924,7 +2811,7 @@

    -
    +
    module @@ -2945,7 +2832,7 @@

    -
    +
    module @@ -2980,7 +2867,7 @@

    -
    +
    module @@ -2994,7 +2881,7 @@

    -
    +
    type new_t = .. @@ -3002,26 +2889,24 @@

    -
    +
    type new_t += - - - - -
    - | C - -
    +
      +
    1. + + | C + +
    2. +
    -
    +
    module diff --git a/test/generators/html/Recent-X.html b/test/generators/html/Recent-X.html index e6dd225e1d..481a4c9932 100644 --- a/test/generators/html/Recent-X.html +++ b/test/generators/html/Recent-X.html @@ -15,7 +15,7 @@

    Module Recent.X

    -
    +
    module L := @@ -25,7 +25,7 @@

    Module Recent.X

    -
    +
    type t = @@ -35,7 +35,7 @@

    Module Recent.X

    -
    +
    type u := int @@ -43,7 +43,7 @@

    Module Recent.X

    -
    +
    type v = diff --git a/test/generators/html/Recent-Z-Y-X.html b/test/generators/html/Recent-Z-Y-X.html index a8a5b3844b..c114eee5a4 100644 --- a/test/generators/html/Recent-Z-Y-X.html +++ b/test/generators/html/Recent-Z-Y-X.html @@ -16,7 +16,7 @@
    -
    +
    type 'a t diff --git a/test/generators/html/Recent-Z-Y.html b/test/generators/html/Recent-Z-Y.html index 8ffae7a0d7..6e7206a879 100644 --- a/test/generators/html/Recent-Z-Y.html +++ b/test/generators/html/Recent-Z-Y.html @@ -15,7 +15,7 @@
    -
    +
    module diff --git a/test/generators/html/Recent-Z.html b/test/generators/html/Recent-Z.html index 17575b8145..ab0767a9a4 100644 --- a/test/generators/html/Recent-Z.html +++ b/test/generators/html/Recent-Z.html @@ -15,7 +15,7 @@

    Module Recent.Z

    -
    +
    module diff --git a/test/generators/html/Recent-module-type-PolyS.html b/test/generators/html/Recent-module-type-PolyS.html index 7252cc31e3..6bee3b33b4 100644 --- a/test/generators/html/Recent-module-type-PolyS.html +++ b/test/generators/html/Recent-module-type-PolyS.html @@ -16,23 +16,21 @@

    Module type Recent.PolyS

    -
    +
    type t = [ - - - - - - - -
    - | `A -
    - | `B -
    ] +
      +
    1. + | + `A +
    2. +
    3. + | + `B +
    4. +
    ]
    diff --git a/test/generators/html/Recent-module-type-S1.html b/test/generators/html/Recent-module-type-S1.html index ab90be6eee..f26854814c 100644 --- a/test/generators/html/Recent-module-type-S1.html +++ b/test/generators/html/Recent-module-type-S1.html @@ -22,7 +22,7 @@

    Module type Recent.S1

    Parameters

    -
    +
    module _ diff --git a/test/generators/html/Recent.html b/test/generators/html/Recent.html index 925d34138a..907983fab5 100644 --- a/test/generators/html/Recent.html +++ b/test/generators/html/Recent.html @@ -12,7 +12,7 @@

    Module Recent

    -
    +
    module @@ -26,7 +26,7 @@

    Module Recent

    -
    +
    module @@ -43,168 +43,140 @@

    Module Recent

    -
    +
    type variant = - - - - - - - - - - - - - - - - - - -
    - - | A - -
    - - | - B - of int - - -
    - - | C - - (*

    foo

    +
      +
    1. + + | A + +
    2. +
    3. + + | + B + of int + + +
    4. +
    5. + + | C + +
      (*

      foo

      *) -
    - - | D - - (* + + +
  • + + | D + +
    (*

    bar

    *) -
  • - - | - E - of - { - - - - - -
    - - a : int; -
    } -
    +
    + +
  • + + | + E + of + { + +
      +
    1. + + a : int; +
    2. +
    } +
  • +
    -
    +
    type _ gadt = - - - - - - - - - - - -
    - - | - A : - int gadt - - -
    - - | - B : int - -> - string gadt - - - (*

    foo

    +
      +
    1. + + | + A : + int gadt + + +
    2. +
    3. + + | + B : int + -> + string gadt + + +
      (*

      foo

      *) -
    - - | - C : { - - - - - -
    - - a : int; -
    - } - -> - unit gadt - - -
    +
    + +
  • + + | + C : { + +
      +
    1. + + a : int; +
    2. +
    + } + -> + unit gadt + + +
  • +
    -
    +
    type polymorphic_variant = [ - - - - - - - - - - - - - - - -
    - - | `A -
    - - | - `B of int -
    - - | `C - (*

    foo

    +
      +
    1. + + | `A +
    2. +
    3. + + | + `B of int +
    4. +
    5. + + | `C +
      (*

      foo

      *) -
    - - | `D - (*

    bar

    + + +
  • + + | `D +
    (*

    bar

    *) -
  • ] +
    + + ]
    -
    +
    type empty_variant = | @@ -212,7 +184,7 @@

    Module Recent

    -
    +
    type @@ -222,57 +194,53 @@

    Module Recent

    -
    +
    type empty_conj = - - - - -
    - - | - X : - [< - `X of & 'a & int - * float - ] - -> - empty_conj - - -
    +
      +
    1. + + | + X : + [< + `X of & 'a & int + * float + ] + -> + empty_conj + + +
    2. +
    -
    +
    type conj = - - - - -
    - - | - X : - [< - `X of int & - [< `B of int & float ] - ] - -> - conj - - -
    +
      +
    1. + + | + X : + [< + `X of int & + [< `B of int & float ] + ] + -> + conj + + +
    2. +
    -
    +
    val empty_conj : @@ -285,7 +253,7 @@

    Module Recent

    -
    +
    val conj : @@ -299,7 +267,7 @@

    Module Recent

    -
    +
    module Z @@ -311,7 +279,7 @@

    Module Recent

    -
    +
    module X @@ -323,7 +291,7 @@

    Module Recent

    -
    +
    module diff --git a/test/generators/html/Recent_impl-B.html b/test/generators/html/Recent_impl-B.html index 13883db938..2e97bb0a2d 100644 --- a/test/generators/html/Recent_impl-B.html +++ b/test/generators/html/Recent_impl-B.html @@ -16,19 +16,17 @@

    Module Recent_impl.B

    -
    +
    type t = - - - - -
    - - | B - -
    +
      +
    1. + + | B + +
    2. +
    diff --git a/test/generators/html/Recent_impl-Foo-A.html b/test/generators/html/Recent_impl-Foo-A.html index 351c17ef6b..50acde4387 100644 --- a/test/generators/html/Recent_impl-Foo-A.html +++ b/test/generators/html/Recent_impl-Foo-A.html @@ -17,19 +17,17 @@

    Module Foo.A

    -
    +
    type t = - - - - -
    - - | A - -
    +
      +
    1. + + | A + +
    2. +
    diff --git a/test/generators/html/Recent_impl-Foo-B.html b/test/generators/html/Recent_impl-Foo-B.html index b7d13d488b..cee19d8771 100644 --- a/test/generators/html/Recent_impl-Foo-B.html +++ b/test/generators/html/Recent_impl-Foo-B.html @@ -17,19 +17,17 @@

    Module Foo.B

    -
    +
    type t = - - - - -
    - - | B - -
    +
      +
    1. + + | B + +
    2. +
    diff --git a/test/generators/html/Recent_impl-Foo.html b/test/generators/html/Recent_impl-Foo.html index e0dffafb93..1667292b62 100644 --- a/test/generators/html/Recent_impl-Foo.html +++ b/test/generators/html/Recent_impl-Foo.html @@ -16,7 +16,7 @@

    Module Recent_impl.Foo

    -
    +
    module @@ -29,7 +29,7 @@

    Module Recent_impl.Foo

    -
    +
    module diff --git a/test/generators/html/Recent_impl-module-type-S-F.html b/test/generators/html/Recent_impl-module-type-S-F.html index 39aab55c66..6ed14b54da 100644 --- a/test/generators/html/Recent_impl-module-type-S-F.html +++ b/test/generators/html/Recent_impl-module-type-S-F.html @@ -23,7 +23,7 @@

    Parameters

    -
    +
    module _ @@ -36,7 +36,7 @@

    Parameters

    Signature

    -
    +
    type t
    diff --git a/test/generators/html/Recent_impl-module-type-S.html b/test/generators/html/Recent_impl-module-type-S.html index 8f9fe023ca..7fc01af909 100644 --- a/test/generators/html/Recent_impl-module-type-S.html +++ b/test/generators/html/Recent_impl-module-type-S.html @@ -16,7 +16,7 @@

    Module type Recent_impl.S

    -
    +
    module @@ -31,7 +31,7 @@

    Module type Recent_impl.S

    -
    +
    module @@ -44,7 +44,7 @@

    Module type Recent_impl.S

    -
    +
    val f : diff --git a/test/generators/html/Recent_impl.html b/test/generators/html/Recent_impl.html index e8bf6687b2..f64fe452b3 100644 --- a/test/generators/html/Recent_impl.html +++ b/test/generators/html/Recent_impl.html @@ -13,7 +13,7 @@

    Module Recent_impl

    -
    +
    module @@ -26,7 +26,7 @@

    Module Recent_impl

    -
    +
    module @@ -39,13 +39,13 @@

    Module Recent_impl

    -
    +
    type u
    -
    +
    module @@ -59,7 +59,7 @@

    Module Recent_impl

    -
    +
    module B' = Foo.B diff --git a/test/generators/html/Section.html b/test/generators/html/Section.html index a980a8efcb..c549cc2639 100644 --- a/test/generators/html/Section.html +++ b/test/generators/html/Section.html @@ -46,7 +46,7 @@

    Aside only

    Value only

    -
    +
    val foo : unit
    diff --git a/test/generators/html/Stop-N.html b/test/generators/html/Stop-N.html index ac2abcc72b..c17ea4132b 100644 --- a/test/generators/html/Stop-N.html +++ b/test/generators/html/Stop-N.html @@ -15,7 +15,7 @@

    Module Stop.N

    -
    +
    val quux : int
    diff --git a/test/generators/html/Stop.html b/test/generators/html/Stop.html index ea577eec90..cc3634a6af 100644 --- a/test/generators/html/Stop.html +++ b/test/generators/html/Stop.html @@ -13,7 +13,7 @@

    Module Stop

    -
    +
    val foo : int

    This is normal commented text.

    @@ -30,7 +30,7 @@

    Module Stop

    only in that module, and not in this outer module.

    -
    +
    module N @@ -42,7 +42,7 @@

    Module Stop

    -
    +
    val lol : int
    diff --git a/test/generators/html/Stop_dead_link_doc-Foo.html b/test/generators/html/Stop_dead_link_doc-Foo.html index 50330538b2..aa277fcf14 100644 --- a/test/generators/html/Stop_dead_link_doc-Foo.html +++ b/test/generators/html/Stop_dead_link_doc-Foo.html @@ -17,7 +17,7 @@

    Module Stop_dead_link_doc.Foo

    -
    +
    type t
    diff --git a/test/generators/html/Stop_dead_link_doc.html b/test/generators/html/Stop_dead_link_doc.html index 193bfc3ae0..abb28e1f85 100644 --- a/test/generators/html/Stop_dead_link_doc.html +++ b/test/generators/html/Stop_dead_link_doc.html @@ -13,7 +13,7 @@

    Module Stop_dead_link_doc

    -
    +
    module @@ -26,119 +26,109 @@

    Module Stop_dead_link_doc

    -
    +
    type foo = - - - - -
    - - | - Bar - of - Foo.t - - -
    +
      +
    1. + + | + Bar + of + Foo.t + + +
    2. +
    -
    +
    type bar = - - - - -
    - - | - Bar - of - { - - - - - -
    - - - field : - Foo.t; - - -
    } -
    +
      +
    1. + + | + Bar + of + { + +
        +
      1. + + + field : + Foo.t; + + +
      2. +
      } +
    2. +
    -
    +
    type foo_ = - - - - -
    - - | - Bar_ - of int * - Foo.t * int - - -
    +
      +
    1. + + | + Bar_ + of int * + Foo.t * int + + +
    2. +
    -
    +
    type bar_ = - - - - -
    - - | - Bar__ - of - Foo.t option - +
      +
    1. + + | + Bar__ + of + Foo.t option - -
    + +
    + +
    -
    +
    type another_foo
    -
    +
    type another_bar
    -
    +
    type another_foo_
    -
    +
    type another_bar_
    diff --git a/test/generators/html/Toplevel_comments-Alias.html b/test/generators/html/Toplevel_comments-Alias.html index e3cf587c48..7d1bc894bd 100644 --- a/test/generators/html/Toplevel_comments-Alias.html +++ b/test/generators/html/Toplevel_comments-Alias.html @@ -17,7 +17,7 @@

    Module Toplevel_comments.Alias

    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-Comments_on_open-M.html b/test/generators/html/Toplevel_comments-Comments_on_open-M.html index 64c15f9761..80bc044658 100644 --- a/test/generators/html/Toplevel_comments-Comments_on_open-M.html +++ b/test/generators/html/Toplevel_comments-Comments_on_open-M.html @@ -19,7 +19,7 @@

    Module Comments_on_open.M

    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-Comments_on_open.html b/test/generators/html/Toplevel_comments-Comments_on_open.html index e317cbc6e8..8f248639d6 100644 --- a/test/generators/html/Toplevel_comments-Comments_on_open.html +++ b/test/generators/html/Toplevel_comments-Comments_on_open.html @@ -19,7 +19,7 @@

    Module Toplevel_comments.Comments_on_open
    -
    +
    module diff --git a/test/generators/html/Toplevel_comments-Include_inline'.html b/test/generators/html/Toplevel_comments-Include_inline'.html index 0c5a359308..9dba44586d 100644 --- a/test/generators/html/Toplevel_comments-Include_inline'.html +++ b/test/generators/html/Toplevel_comments-Include_inline'.html @@ -20,7 +20,7 @@

    Module Toplevel_comments.Include_inline'

    part 3

    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-Include_inline.html b/test/generators/html/Toplevel_comments-Include_inline.html index 1b6349bd0a..7921ce5859 100644 --- a/test/generators/html/Toplevel_comments-Include_inline.html +++ b/test/generators/html/Toplevel_comments-Include_inline.html @@ -19,7 +19,7 @@

    Module Toplevel_comments.Include_inline

    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-Ref_in_synopsis.html b/test/generators/html/Toplevel_comments-Ref_in_synopsis.html index 24ac19ff4c..5f9237183d 100644 --- a/test/generators/html/Toplevel_comments-Ref_in_synopsis.html +++ b/test/generators/html/Toplevel_comments-Ref_in_synopsis.html @@ -21,7 +21,7 @@

    Module Toplevel_comments.Ref_in_synopsis
    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-module-type-Include_inline_T'.html b/test/generators/html/Toplevel_comments-module-type-Include_inline_T'.html index 2f03ddcc67..d57ed15b98 100644 --- a/test/generators/html/Toplevel_comments-module-type-Include_inline_T'.html +++ b/test/generators/html/Toplevel_comments-module-type-Include_inline_T'.html @@ -21,7 +21,7 @@

    Module type

    part 3

    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-module-type-Include_inline_T.html b/test/generators/html/Toplevel_comments-module-type-Include_inline_T.html index ff08b4f67e..3318bf979a 100644 --- a/test/generators/html/Toplevel_comments-module-type-Include_inline_T.html +++ b/test/generators/html/Toplevel_comments-module-type-Include_inline_T.html @@ -20,7 +20,7 @@

    Module type
    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments-module-type-T.html b/test/generators/html/Toplevel_comments-module-type-T.html index e91317819b..97a931ab2a 100644 --- a/test/generators/html/Toplevel_comments-module-type-T.html +++ b/test/generators/html/Toplevel_comments-module-type-T.html @@ -17,7 +17,7 @@

    Module type Toplevel_comments.T

    -
    +
    type t
    diff --git a/test/generators/html/Toplevel_comments.html b/test/generators/html/Toplevel_comments.html index 99746fe19a..85165f94f6 100644 --- a/test/generators/html/Toplevel_comments.html +++ b/test/generators/html/Toplevel_comments.html @@ -16,7 +16,7 @@

    Module Toplevel_comments

    -
    +
    module @@ -30,7 +30,7 @@

    Module Toplevel_comments

    Doc of T, part 1.

    -
    +
    module @@ -43,7 +43,7 @@

    Module Toplevel_comments

    Doc of T, part 2.

    -
    +
    module @@ -58,8 +58,7 @@

    Module Toplevel_comments

    -
    +
    module @@ -75,8 +74,7 @@

    Module Toplevel_comments

    Doc of T, part 2.

    -
    +
    module @@ -95,7 +93,7 @@

    Module Toplevel_comments

    -
    +
    module @@ -108,7 +106,7 @@

    Module Toplevel_comments

    Doc of M

    -
    +
    module @@ -122,7 +120,7 @@

    Module Toplevel_comments

    Doc of M' from outside

    -
    +
    module @@ -135,7 +133,7 @@

    Module Toplevel_comments

    Doc of M'', part 1.

    -
    +
    module @@ -146,7 +144,7 @@

    Module Toplevel_comments

    Doc of Alias.

    -
    +
    class c1 @@ -158,7 +156,7 @@

    Module Toplevel_comments

    Doc of c1, part 1.

    -
    +
    class @@ -172,7 +170,7 @@

    Module Toplevel_comments

    Doc of ct, part 1.

    -
    +
    class c2 @@ -181,7 +179,7 @@

    Module Toplevel_comments

    Doc of c2.

    -
    +
    module @@ -200,7 +198,7 @@

    Module Toplevel_comments

    -
    +
    module diff --git a/test/generators/html/Type-module-type-X.html b/test/generators/html/Type-module-type-X.html index fbb496bf25..965980d0b8 100644 --- a/test/generators/html/Type-module-type-X.html +++ b/test/generators/html/Type-module-type-X.html @@ -15,13 +15,13 @@

    Module type Type.X

    -
    +
    type t
    -
    +
    type u
    diff --git a/test/generators/html/Type.html b/test/generators/html/Type.html index fffc4456b5..9c5849931a 100644 --- a/test/generators/html/Type.html +++ b/test/generators/html/Type.html @@ -12,13 +12,13 @@

    Module Type

    -
    +
    type abstract

    Some documentation.

    -
    +
    type alias = int @@ -26,7 +26,7 @@

    Module Type

    -
    +
    type private_ = private int @@ -34,7 +34,7 @@

    Module Type

    -
    +
    type 'a constructor @@ -43,7 +43,7 @@

    Module Type

    -
    +
    type arrow = int -> int @@ -52,7 +52,7 @@

    Module Type

    -
    +
    type higher_order = @@ -65,7 +65,7 @@

    Module Type

    -
    +
    type labeled = l:int -> int @@ -74,7 +74,7 @@

    Module Type

    -
    +
    type optional = ?l:int -> int @@ -83,7 +83,7 @@

    Module Type

    -
    +
    type labeled_higher_order @@ -101,7 +101,7 @@

    Module Type

    -
    +
    type pair = int * int @@ -109,7 +109,7 @@

    Module Type

    -
    +
    type parens_dropped = int * int @@ -117,7 +117,7 @@

    Module Type

    -
    +
    type triple = int * int * int @@ -125,7 +125,7 @@

    Module Type

    -
    +
    type nested_pair = (int * int) * int @@ -133,7 +133,7 @@

    Module Type

    -
    +
    type instance = int constructor @@ -142,7 +142,7 @@

    Module Type

    -
    +
    type long = @@ -196,314 +196,266 @@

    Module Type

    -
    +
    type variant_e = { - - - - -
    - - a : int; -
    } +
      +
    1. + + a : int; +
    2. +
    }
    -
    +
    type variant = - - - - - - - - - - - - - - - - - - -
    - - | A - -
    - - | - B - of int - - -
    - - | C - - (*

    foo

    +
      +
    1. + + | A + +
    2. +
    3. + + | + B + of int + + +
    4. +
    5. + + | C + +
      (*

      foo

      *) -
    - - | D - - (* + + +
  • + + | D + +
    (*

    bar

    *) -
  • - - | - E - of - variant_e - - -
    -
    -
    -
    -
    +
    + +
  • + + | + E + of + variant_e + + +
  • + +
    +
    +
    +
    type variant_c = { - - - - -
    - - a : int; -
    } +
      +
    1. + + a : int; +
    2. +
    }
    -
    +
    type _ gadt = - - - - - - - - - - -
    - - | - A : - int gadt - - -
    - - | - B : int - -> - string gadt - - -
    - - | - C : - variant_c - -> - unit gadt - - -
    -
    -
    -
    -
    +
      +
    1. + + | + A : + int gadt + + +
    2. +
    3. + + | + B : int + -> + string gadt + + +
    4. +
    5. + + | + C : + variant_c + -> + unit gadt + + +
    6. +
    +
    +
    +
    +
    type degenerate_gadt = - - - - -
    - - | - A : - degenerate_gadt - - -
    +
      +
    1. + | + A : + degenerate_gadt + + +
    2. +
    -
    +
    type private_variant = private - - - - -
    - - | A - -
    +
      +
    1. + | A + +
    2. +
    -
    +
    type record = { - - - - - - - - - - - - - - - - - - -
    - - a : int; -
    - - mutable b : int; - -
    - - c : int; - (*

    foo

    +
      +
    1. + + a : int; +
    2. +
    3. + + mutable b : int; + +
    4. +
    5. + + c : int; +
      (*

      foo

      *) -
    - - d : int; - (* + + +
  • + + d : int; +
    (*

    bar

    *) -
  • - - e : 'a. 'a; -
    } +
    + +
  • + + e : 'a. 'a; +
  • + }
    -
    +
    type polymorphic_variant = [ - - - - - - - - - - - - - -
    - - | `A -
    - - | - `B of int -
    - - | - `C of int * unit - -
    - - | `D -
    ] -
    -
    -
    -
    +
      +
    1. + + | `A +
    2. +
    3. + + | + `B of int +
    4. +
    5. + + | + `C of int * unit + +
    6. +
    7. + + | `D +
    8. +
    ] +
    +
    +
    +
    type polymorphic_variant_extension = [ - - - - - - - -
    - - | - - polymorphic_variant - - -
    - - | `E -
    ] -
    -
    -
    -
    +
      +
    1. + + | + + polymorphic_variant + + +
    2. +
    3. + + | `E +
    4. +
    ] +
    +
    +
    +
    type nested_polymorphic_variant = [ - - - - -
    - - | - - `A of - [ `B | `C ] - - -
    ] +
      +
    1. + + | + + `A of + [ `B | `C ] + + +
    2. +
    ]
    -
    +
    type private_extenion#row @@ -511,28 +463,27 @@

    Module Type

    -
    +
    and private_extenion = private [> - - - - -
    - - | - - polymorphic_variant - - -
    ] +
      +
    1. + + | + + polymorphic_variant + + +
    2. +
    ]
    -
    +
    type object_ = < a : int ; b : int ; c : int > @@ -540,7 +491,7 @@

    Module Type

    -
    +
    module @@ -554,7 +505,7 @@

    Module Type

    -
    +
    type module_ = @@ -566,7 +517,7 @@

    Module Type

    -
    +
    type module_substitution = @@ -582,7 +533,7 @@

    Module Type

    -
    +
    type +'a covariant @@ -591,7 +542,7 @@

    Module Type

    -
    +
    type -'a contravariant @@ -600,7 +551,7 @@

    Module Type

    -
    +
    type _ bivariant @@ -609,7 +560,7 @@

    Module Type

    -
    +
    type ('a, 'b) binary @@ -618,7 +569,7 @@

    Module Type

    -
    +
    type using_binary = @@ -628,7 +579,7 @@

    Module Type

    -
    +
    type 'custom name @@ -637,7 +588,7 @@

    Module Type

    -
    +
    type 'a constrained @@ -649,7 +600,7 @@

    Module Type

    -
    +
    type 'a exact_variant @@ -662,7 +613,7 @@

    Module Type

    -
    +
    type 'a lower_variant @@ -675,7 +626,7 @@

    Module Type

    -
    +
    type 'a any_variant @@ -687,7 +638,7 @@

    Module Type

    -
    +
    type 'a upper_variant @@ -700,7 +651,7 @@

    Module Type

    -
    +
    type 'a named_variant @@ -715,7 +666,7 @@

    Module Type

    -
    +
    type 'a exact_object @@ -728,7 +679,7 @@

    Module Type

    -
    +
    type 'a lower_object @@ -741,7 +692,7 @@

    Module Type

    -
    +
    type 'a poly_object @@ -754,7 +705,7 @@

    Module Type

    -
    +
    type @@ -772,7 +723,7 @@

    Module Type

    -
    +
    type as_ = int as 'a * @@ -782,7 +733,7 @@

    Module Type

    -
    +
    type extensible = .. @@ -790,89 +741,81 @@

    Module Type

    -
    +
    + type extensible += - - - - - - - - - -
    - - | - Extension - - (* +
      +
    1. + + | + Extension + +
      (*

      Documentation for Extension.

      *) -
    - - | - Another_extension - - (* + + +
  • + + | + Another_extension + +
    (*

    Documentation for Another_extension .

    *) -
  • +
    + +
    -
    +
    type mutually = - - - - -
    - - | - A - of - recursive - - -
    +
      +
    1. + + | + A + of + recursive + + +
    2. +
    -
    +
    and recursive = - - - - -
    - - | - B - of - mutually - - -
    +
      +
    1. + + | + B + of + mutually + + +
    2. +
    -
    +
    exception Foo diff --git a/test/generators/html/Val.html b/test/generators/html/Val.html index 678b5b53f5..8625ded69e 100644 --- a/test/generators/html/Val.html +++ b/test/generators/html/Val.html @@ -11,21 +11,21 @@
    -
    +
    val documented : unit

    Foo.

    -
    +
    val undocumented : unit
    -
    +
    val documented_above : unit diff --git a/test/xref2/canonical_hidden_module.t/run.t b/test/xref2/canonical_hidden_module.t/run.t index f3f9d126c4..5b5e51cf28 100644 --- a/test/xref2/canonical_hidden_module.t/run.t +++ b/test/xref2/canonical_hidden_module.t/run.t @@ -83,7 +83,7 @@ See the comments on the types at the end of test.mli for the expectation.
    -
    +
    module @@ -96,7 +96,7 @@ See the comments on the types at the end of test.mli for the expectation.
    -
    +
    module A @@ -109,7 +109,7 @@ See the comments on the types at the end of test.mli for the expectation.

    This should not have an expansion

    -
    +
    module B @@ -121,7 +121,7 @@ See the comments on the types at the end of test.mli for the expectation.

    This should have an expansion

    -
    +
    module C @@ -133,7 +133,7 @@ See the comments on the types at the end of test.mli for the expectation.

    This should have an expansion

    -
    +
    module D @@ -146,7 +146,7 @@ See the comments on the types at the end of test.mli for the expectation.

    This also should have an expansion

    -
    +
    type a = A.t @@ -159,7 +159,7 @@ See the comments on the types at the end of test.mli for the expectation.
    -
    +
    type b
    @@ -170,7 +170,7 @@ See the comments on the types at the end of test.mli for the expectation.
    -
    +
    type c = C.t @@ -181,7 +181,7 @@ See the comments on the types at the end of test.mli for the expectation.
    -
    +
    type d = D.t diff --git a/test/xref2/labels/labels.t/run.t b/test/xref2/labels/labels.t/run.t index 602316f2eb..a8f03d6662 100644 --- a/test/xref2/labels/labels.t/run.t +++ b/test/xref2/labels/labels.t/run.t @@ -100,7 +100,7 @@ The second occurence of 'B' in the main page should be disambiguated

    First label

    Floating label

    -
    +
    module M @@ -112,7 +112,7 @@ The second occurence of 'B' in the main page should be disambiguated
    -
    +
    module N diff --git a/test/xref2/module_preamble.t/run.t b/test/xref2/module_preamble.t/run.t index ef2247fa54..d4d3822a74 100644 --- a/test/xref2/module_preamble.t/run.t +++ b/test/xref2/module_preamble.t/run.t @@ -47,7 +47,7 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered
    -
    +
    module B @@ -95,7 +95,7 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered the "content".

    -
    +
    type t