diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md index c47d72252a..547448115b 100644 --- a/test/generators/markdown/Alias.X.md +++ b/test/generators/markdown/Alias.X.md @@ -2,7 +2,7 @@ AliasX Module `` Alias.X `` -######   type t = int +###### type t = int Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' diff --git a/test/generators/markdown/Alias.md b/test/generators/markdown/Alias.md index 6127d28baf..b939f15fd4 100644 --- a/test/generators/markdown/Alias.md +++ b/test/generators/markdown/Alias.md @@ -2,15 +2,15 @@ Alias Module `` Alias `` -######   module X : sig ... - ######   end +###### module X : sig ... +###### end AliasX Module `` Alias.X `` -######   type t = int +###### type t = int Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index 9d828dbced..844ef6ecc9 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -2,12 +2,12 @@ Bugs Module `` Bugs `` -######   type 'a opt = 'a option +###### type 'a opt = 'a option -######   val foo : ?bar:'a -> unit -> unit +###### val foo : ?bar:'a -> unit -> unit Triggers an assertion failure when https://github.com/ocaml/odoc/issues/101 is not fixed. diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index eeb2b4054f..809ee304bf 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -6,15 +6,15 @@ Bugs_post_406 Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 -######   class type let_open = object +###### class type let_open = object - ######   end +###### end -######   class let_open' : object ... - ######   end +###### class let_open' : object ... +###### end Bugs_post_406let_open diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md index 3cdc286647..0d13d95b5a 100644 --- a/test/generators/markdown/Class.md +++ b/test/generators/markdown/Class.md @@ -2,57 +2,57 @@ Class Module `` Class `` -######   class type empty = object +###### class type empty = object - ######   end +###### end -######   class type mutually = object +###### class type mutually = object - ######   end +###### end -######   class type recursive = object +###### class type recursive = object - ######   end +###### end -######   class mutually' : mutually +###### class mutually' : mutually -######   class recursive' : recursive +###### class recursive' : recursive -######   class type virtual empty_virtual = object +###### class type virtual empty_virtual = object - ######   end +###### end -######   class virtual empty_virtual' : empty +###### class virtual empty_virtual' : empty -######   class type 'a polymorphic = object +###### class type 'a polymorphic = object - ######   end +###### end -######   class 'a polymorphic' : 'a polymorphic +###### class 'a polymorphic' : 'a polymorphic Classempty diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md index 79eefe08ce..896a441142 100644 --- a/test/generators/markdown/External.md +++ b/test/generators/markdown/External.md @@ -2,7 +2,7 @@ External Module `` External `` -######   val foo : unit -> unit +###### val foo : unit -> unit Foo _bar_. diff --git a/test/generators/markdown/Functor.F1.md b/test/generators/markdown/Functor.F1.md index 0a64d0856c..4c79828192 100644 --- a/test/generators/markdown/Functor.F1.md +++ b/test/generators/markdown/Functor.F1.md @@ -2,32 +2,32 @@ FunctorF1 Module `` Functor.F1 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t +###### type t FunctorF11-Arg Parameter `` F1.1-Arg `` -######   type t +###### type t diff --git a/test/generators/markdown/Functor.F2.md b/test/generators/markdown/Functor.F2.md index a2d9b633b0..2abd7fdd8a 100644 --- a/test/generators/markdown/Functor.F2.md +++ b/test/generators/markdown/Functor.F2.md @@ -2,32 +2,32 @@ FunctorF2 Module `` Functor.F2 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t = Arg.t +###### type t = Arg.t FunctorF21-Arg Parameter `` F2.1-Arg `` -######   type t +###### type t diff --git a/test/generators/markdown/Functor.F3.md b/test/generators/markdown/Functor.F3.md index 3ccd8595d3..bd0bfa1c12 100644 --- a/test/generators/markdown/Functor.F3.md +++ b/test/generators/markdown/Functor.F3.md @@ -2,32 +2,32 @@ FunctorF3 Module `` Functor.F3 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t = Arg.t +###### type t = Arg.t FunctorF31-Arg Parameter `` F3.1-Arg `` -######   type t +###### type t diff --git a/test/generators/markdown/Functor.F4.md b/test/generators/markdown/Functor.F4.md index 9be64acb36..19a2c2d3f3 100644 --- a/test/generators/markdown/Functor.F4.md +++ b/test/generators/markdown/Functor.F4.md @@ -2,32 +2,32 @@ FunctorF4 Module `` Functor.F4 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t +###### type t FunctorF41-Arg Parameter `` F4.1-Arg `` -######   type t +###### type t diff --git a/test/generators/markdown/Functor.F5.md b/test/generators/markdown/Functor.F5.md index d6095a2726..02db8fcc0f 100644 --- a/test/generators/markdown/Functor.F5.md +++ b/test/generators/markdown/Functor.F5.md @@ -2,13 +2,13 @@ FunctorF5 Module `` Functor.F5 `` -# Parameters +#:parameters Parameters -# Signature +#:signature Signature -######   type t +###### type t diff --git a/test/generators/markdown/Functor.md b/test/generators/markdown/Functor.md index 2fdb5ee233..79988a3cf4 100644 --- a/test/generators/markdown/Functor.md +++ b/test/generators/markdown/Functor.md @@ -2,19 +2,19 @@ Functor Module `` Functor `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end -######   module type S1 = sig +###### module type S1 = sig ## Parameters @@ -25,11 +25,11 @@ Functor ######         module _ : sig -######                                 type t +######                 type t - ######   end +######         end @@ -43,223 +43,223 @@ Functor - ######   end +###### end -######   module F1 (Arg : S) : S +###### module F1 (Arg : S) : S -######   module F2 (Arg : S) : S with type t = Arg.t +###### module F2 (Arg : S) : S with type t = Arg.t -######   module F3 (Arg : S) : sig ... - ######   end +###### module F3 (Arg : S) : sig ... +###### end -######   module F4 (Arg : S) : S +###### module F4 (Arg : S) : S -######   module F5 () : S +###### module F5 () : S FunctorS Module type `` Functor.S `` -######   type t +###### type t FunctorS1 Module type `` Functor.S1 `` -# Parameters +#:parameters Parameters -######   module _ : sig +###### module _ : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t +###### type t FunctorS11-_ Parameter `` S1.1-_ `` -######   type t +###### type t FunctorF1 Module `` Functor.F1 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t +###### type t FunctorF11-Arg Parameter `` F1.1-Arg `` -######   type t +###### type t FunctorF2 Module `` Functor.F2 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t = Arg.t +###### type t = Arg.t FunctorF21-Arg Parameter `` F2.1-Arg `` -######   type t +###### type t FunctorF3 Module `` Functor.F3 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t = Arg.t +###### type t = Arg.t FunctorF31-Arg Parameter `` F3.1-Arg `` -######   type t +###### type t FunctorF4 Module `` Functor.F4 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type t +###### type t FunctorF41-Arg Parameter `` F4.1-Arg `` -######   type t +###### type t FunctorF5 Module `` Functor.F5 `` -# Parameters +#:parameters Parameters -# Signature +#:signature Signature -######   type t +###### type t diff --git a/test/generators/markdown/Functor2.X.md b/test/generators/markdown/Functor2.X.md index 6c45900e93..0128da7725 100644 --- a/test/generators/markdown/Functor2.X.md +++ b/test/generators/markdown/Functor2.X.md @@ -2,61 +2,61 @@ Functor2X Module `` Functor2.X `` -# Parameters +#:parameters Parameters -######   module Y : sig +###### module Y : sig ######         type t - ######   end +###### end -######   module Z : sig +###### module Z : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type y_t = Y.t +###### type y_t = Y.t -######   type z_t = Z.t +###### type z_t = Z.t -######   type x_t = y_t +###### type x_t = y_t Functor2X1-Y Parameter `` X.1-Y `` -######   type t +###### type t Functor2X2-Z Parameter `` X.2-Z `` -######   type t +###### type t diff --git a/test/generators/markdown/Functor2.md b/test/generators/markdown/Functor2.md index 9e8733256e..ec6ebdcadd 100644 --- a/test/generators/markdown/Functor2.md +++ b/test/generators/markdown/Functor2.md @@ -2,25 +2,25 @@ Functor2 Module `` Functor2 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end -######   module X (Y : S) (Z : S) : sig ... - ######   end +###### module X (Y : S) (Z : S) : sig ... +###### end -######   module type XF = sig +###### module type XF = sig ## Parameters @@ -31,11 +31,11 @@ Functor2 ######         module Y : sig -######                                 type t +######                 type t - ######   end +######         end @@ -43,11 +43,11 @@ Functor2 ######         module Z : sig -######                                 type t +######                 type t - ######   end +######         end @@ -71,138 +71,138 @@ Functor2 - ######   end +###### end Functor2S Module type `` Functor2.S `` -######   type t +###### type t Functor2X Module `` Functor2.X `` -# Parameters +#:parameters Parameters -######   module Y : sig +###### module Y : sig ######         type t - ######   end +###### end -######   module Z : sig +###### module Z : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type y_t = Y.t +###### type y_t = Y.t -######   type z_t = Z.t +###### type z_t = Z.t -######   type x_t = y_t +###### type x_t = y_t Functor2X1-Y Parameter `` X.1-Y `` -######   type t +###### type t Functor2X2-Z Parameter `` X.2-Z `` -######   type t +###### type t Functor2XF Module type `` Functor2.XF `` -# Parameters +#:parameters Parameters -######   module Y : sig +###### module Y : sig ######         type t - ######   end +###### end -######   module Z : sig +###### module Z : sig ######         type t - ######   end +###### end -# Signature +#:signature Signature -######   type y_t = Y.t +###### type y_t = Y.t -######   type z_t = Z.t +###### type z_t = Z.t -######   type x_t = y_t +###### type x_t = y_t Functor2XF1-Y Parameter `` XF.1-Y `` -######   type t +###### type t Functor2XF2-Z Parameter `` XF.2-Z `` -######   type t +###### type t diff --git a/test/generators/markdown/Include.md b/test/generators/markdown/Include.md index 480f4df141..5f7e004b62 100644 --- a/test/generators/markdown/Include.md +++ b/test/generators/markdown/Include.md @@ -2,86 +2,86 @@ Include Module `` Include `` -######   module type Not_inlined = sig +###### module type Not_inlined = sig ######         type t - ######   end +###### end -######   type t +###### type t -######   module type Inlined = sig +###### module type Inlined = sig ######         type u - ######   end +###### end -######   type u +###### type u -######   module type Not_inlined_and_closed = sig +###### module type Not_inlined_and_closed = sig ######         type v - ######   end +###### end include Not_inlined_and_closed -######   module type Not_inlined_and_opened = sig +###### module type Not_inlined_and_opened = sig ######         type w - ######   end +###### end -######   type w +###### type w -######   module type Inherent_Module = sig +###### module type Inherent_Module = sig ######         val a : t - ######   end +###### end -######   module type Dorminant_Module = sig +###### module type Dorminant_Module = sig @@ -90,49 +90,49 @@ include Not_inlined_and_closed - ######   end +###### end -######   val a : u +###### val a : u IncludeNot_inlined Module type `` Include.Not_inlined `` -######   type t +###### type t IncludeInlined Module type `` Include.Inlined `` -######   type u +###### type u IncludeNot_inlined_and_closed Module type `` Include.Not_inlined_and_closed `` -######   type v +###### type v IncludeNot_inlined_and_opened Module type `` Include.Not_inlined_and_opened `` -######   type w +###### type w IncludeInherent_Module Module type `` Include.Inherent_Module `` -######   val a : t +###### val a : t IncludeDorminant_Module @@ -141,5 +141,5 @@ IncludeDorminant_Module -######   val a : u +###### val a : u diff --git a/test/generators/markdown/Include2.X.md b/test/generators/markdown/Include2.X.md index 7c6c6364fa..d7eb15686f 100644 --- a/test/generators/markdown/Include2.X.md +++ b/test/generators/markdown/Include2.X.md @@ -6,5 +6,5 @@ Include2X Comment about X that should not appear when including X below. -######   type t = int +###### type t = int diff --git a/test/generators/markdown/Include2.Y.md b/test/generators/markdown/Include2.Y.md index 42c88c6633..fcdb8e2699 100644 --- a/test/generators/markdown/Include2.Y.md +++ b/test/generators/markdown/Include2.Y.md @@ -6,5 +6,5 @@ Include2Y Top-comment of Y. -######   type t +###### type t diff --git a/test/generators/markdown/Include2.Y_include_doc.md b/test/generators/markdown/Include2.Y_include_doc.md index 3433c0d2e8..97ab8a8fce 100644 --- a/test/generators/markdown/Include2.Y_include_doc.md +++ b/test/generators/markdown/Include2.Y_include_doc.md @@ -2,5 +2,5 @@ Include2Y_include_doc Module `` Include2.Y_include_doc `` -######   type t = Y.t +###### type t = Y.t diff --git a/test/generators/markdown/Include2.Y_include_synopsis.md b/test/generators/markdown/Include2.Y_include_synopsis.md index 2414454e0b..7e416308ff 100644 --- a/test/generators/markdown/Include2.Y_include_synopsis.md +++ b/test/generators/markdown/Include2.Y_include_synopsis.md @@ -6,5 +6,5 @@ Include2Y_include_synopsis The `` include Y `` below should have the synopsis from `` Y `` 's top-comment attached to it. -######   type t = Y.t +###### type t = Y.t diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index 5add57667a..b4c673d3e3 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -2,8 +2,8 @@ Include2 Module `` Include2 `` -######   module X : sig ... - ######   end +###### module X : sig ... +###### end Comment about X that should not appear when including X below. @@ -15,13 +15,13 @@ Comment about X that should not appear when including X below. -######   type t = int +###### type t = int -######   module Y : sig ... - ######   end +###### module Y : sig ... +###### end Top-comment of Y. @@ -29,8 +29,8 @@ Top-comment of Y. -######   module Y_include_synopsis : sig ... - ######   end +###### module Y_include_synopsis : sig ... +###### end The `` include Y `` below should have the synopsis from `` Y `` 's top-comment attached to it. @@ -38,8 +38,8 @@ The `` include Y `` below should have the synopsis from `` Y `` 's top-commen -######   module Y_include_doc : sig ... - ######   end +###### module Y_include_doc : sig ... +###### end Include2X @@ -50,7 +50,7 @@ Include2X Comment about X that should not appear when including X below. -######   type t = int +###### type t = int Include2Y @@ -61,7 +61,7 @@ Include2Y Top-comment of Y. -######   type t +###### type t Include2Y_include_synopsis @@ -72,12 +72,12 @@ Include2Y_include_synopsis The `` include Y `` below should have the synopsis from `` Y `` 's top-comment attached to it. -######   type t = Y.t +###### type t = Y.t Include2Y_include_doc Module `` Include2.Y_include_doc `` -######   type t = Y.t +###### type t = Y.t diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index 2489b478dc..83d6a7c328 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -2,7 +2,7 @@ Include_sections Module `` Include_sections `` -######   module type Something = sig +###### module type Something = sig ######         val something : unit @@ -45,7 +45,7 @@ Some text. - ######   end +###### end A module type. @@ -57,7 +57,7 @@ Let's include `` Something `` once -# Something 1 +#:something-1 Something 1 foo @@ -70,7 +70,7 @@ foo -# Something 1-bis +#:something-1-bis Something 1-bis Some text. @@ -78,7 +78,7 @@ Some text. -# Second include +#:second-include Second include Let's include `` Something `` a second time: the heading level should be shift here. @@ -145,7 +145,7 @@ And let's include it again, but without inlining it this time: the ToC shouldn't -######   val something : unit +###### val something : unit @@ -159,7 +159,7 @@ foo -######   val foo : unit +###### val foo : unit @@ -169,7 +169,7 @@ foo -######   val bar : unit +###### val bar : unit foo bar @@ -192,12 +192,12 @@ Include_sectionsSomething A module type. -######   val something : unit +###### val something : unit -# Something 1 +#:something-1 Something 1 foo @@ -205,7 +205,7 @@ foo -######   val foo : unit +###### val foo : unit @@ -215,7 +215,7 @@ foo -######   val bar : unit +###### val bar : unit foo bar @@ -223,7 +223,7 @@ foo bar -# Something 1-bis +#:something-1-bis Something 1-bis Some text. diff --git a/test/generators/markdown/Interlude.md b/test/generators/markdown/Interlude.md index 9918891098..9387cf6850 100644 --- a/test/generators/markdown/Interlude.md +++ b/test/generators/markdown/Interlude.md @@ -10,7 +10,7 @@ Some separate stray text at the top of the module. -######   val foo : unit +###### val foo : unit Foo. @@ -29,7 +29,7 @@ A separate block of stray text, adjacent to the preceding one. -######   val bar : unit +###### val bar : unit Bar. @@ -37,17 +37,17 @@ Bar. -######   val multiple : unit +###### val multiple : unit -######   val signature : unit +###### val signature : unit -######   val items : unit +###### val items : unit diff --git a/test/generators/markdown/Labels.A.md b/test/generators/markdown/Labels.A.md index 52e1cacf4e..a1234a5085 100644 --- a/test/generators/markdown/Labels.A.md +++ b/test/generators/markdown/Labels.A.md @@ -2,4 +2,4 @@ LabelsA Module `` Labels.A `` -# Attached to module +#:L3 Attached to module diff --git a/test/generators/markdown/Labels.c.md b/test/generators/markdown/Labels.c.md index a8d00769b2..4cf0384642 100644 --- a/test/generators/markdown/Labels.c.md +++ b/test/generators/markdown/Labels.c.md @@ -2,4 +2,4 @@ Labelsc Class `` Labels.c `` -# Attached to class +#:L6 Attached to class diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index bfbf51845e..19c5565b50 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -2,21 +2,21 @@ Labels Module `` Labels `` -# Attached to unit +#:L1 Attached to unit -# Attached to nothing +#:L2 Attached to nothing -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   type t +###### type t Attached to type @@ -24,7 +24,7 @@ Attached to type -######   val f : t +###### val f : t Attached to value @@ -32,7 +32,7 @@ Attached to value -######   val e : unit -> t +###### val e : unit -> t Attached to external @@ -40,37 +40,37 @@ Attached to external -######   module type S = sig +###### module type S = sig ### Attached to module type --- - ######   end +###### end -######   class c : object ... - ######   end +###### class c : object ... +###### end -######   class type cs = object +###### class type cs = object ### Attached to class type --- - ######   end +###### end -######   exception E +###### exception E Attached to exception @@ -78,12 +78,12 @@ Attached to exception -######   type x = .. +###### type x = .. -######   type x += +###### type x += ######         | X @@ -98,7 +98,7 @@ Attached to extension -######   module S := A +###### module S := A Attached to module subst @@ -106,7 +106,7 @@ Attached to module subst -######   type s := t +###### type s := t Attached to type subst @@ -114,7 +114,7 @@ Attached to type subst -######   type u = +###### type u = ######         | A' @@ -128,7 +128,7 @@ Attached to type subst -######   type v = { +###### type v = { ######         `` f : t; `` @@ -174,22 +174,22 @@ LabelsA Module `` Labels.A `` -# Attached to module +#:L3 Attached to module LabelsS Module type `` Labels.S `` -# Attached to module type +#:L6 Attached to module type Labelsc Class `` Labels.c `` -# Attached to class +#:L6 Attached to class Labelscs Class type `` Labels.cs `` -# Attached to class type +#:L7 Attached to class type diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 2314a2c22a..16fe977f4f 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -6,7 +6,7 @@ Markup Here, we test the rendering of comment markup. -# Sections +#:sections Sections Let's get these done first, because sections will be used to break up the rest of this test. @@ -62,7 +62,7 @@ Parts of a longer paragraph that can be considered alone can also have headings. -# Styling +#:styling Styling This paragraph has some styled elements: **bold** and _italic_, **_bold italic_**, _emphasis_, __emphasis_ within emphasis_, **_bold italic_**, superscript, subscript. The line spacing should be enough for superscripts and subscripts not to look odd. @@ -85,7 +85,7 @@ Code can appear **inside `` other `` markup**. Its display shouldn't be affect -# Links and references +#:links-and-references Links and references This is a link. It sends you to the top of this page. Links can have markup inside them: **bold**, _italics_, _emphasis_, superscript, subscript, and `` code `` . Links can also be nested _inside_ markup. Links cannot be nested inside each other. This link has no replacement text: #. The text is filled in by odoc. This is a shorthand link: #. The text is also filled in by odoc in this case. @@ -96,7 +96,7 @@ This is a reference to `` foo `` . References can have replacement text: the va -# Preformatted text +#:preformatted-text Preformatted text This is a code block: @@ -112,10 +112,10 @@ let bar = There are also verbatim blocks: - The main difference is these don't get syntax highlighting. + The main difference is these don't get syntax highlighting. -# Lists +#:lists Lists - This is a @@ -159,7 +159,7 @@ can use explicitly-delimited lists. -# Unicode +#:unicode Unicode The parser supports any ASCII-compatible encoding, in particuλar UTF-8. @@ -167,7 +167,7 @@ The parser supports any ASCII-compatible encoding, in particuλar UTF-8. -# Raw HTML +#:raw-html Raw HTML Raw HTML can be as inline elements into sentences. @@ -176,7 +176,7 @@ Raw HTML can be as inline elements into sentences. -# Modules +#:modules Modules @@ -197,11 +197,10 @@ Raw HTML can be as inline elements into sentences. -# Tags +#:tags Tags -Each comment can - ######   end with zero or more tags. Here are some examples: +Each comment can end with zero or more tags. Here are some examples: @@ -266,7 +265,7 @@ Each comment can -######   val foo : unit +###### val foo : unit Comments in structure items **support** _markup_, too. diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index e8d8ef4d90..937d15d3e5 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -6,7 +6,7 @@ Module Foo. -######   val foo : unit +###### val foo : unit The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See https://caml.inria.fr/mantis/view.php?id=7701. @@ -14,7 +14,7 @@ The module needs at least one signature item, otherwise a bug causes the compile -######   module type S = sig +###### module type S = sig ######         type t @@ -39,26 +39,26 @@ The module needs at least one signature item, otherwise a bug causes the compile ######         module M : sig - ######   end +######         end - ######   end +###### end -######   module type S1 +###### module type S1 -######   module type S2 = S +###### module type S2 = S -######   module type S3 = sig +###### module type S3 = sig ######         type t = int @@ -83,16 +83,16 @@ The module needs at least one signature item, otherwise a bug causes the compile ######         module M : sig - ######   end +######         end - ######   end +###### end -######   module type S4 = sig +###### module type S4 = sig ######         type u @@ -112,16 +112,16 @@ The module needs at least one signature item, otherwise a bug causes the compile ######         module M : sig - ######   end +######         end - ######   end +###### end -######   module type S5 = sig +###### module type S5 = sig ######         type t @@ -141,21 +141,21 @@ The module needs at least one signature item, otherwise a bug causes the compile ######         module M : sig - ######   end +######         end - ######   end +###### end -######   type ('a, 'b) result +###### type ('a, 'b) result -######   module type S6 = sig +###### module type S6 = sig ######         type t @@ -175,22 +175,22 @@ The module needs at least one signature item, otherwise a bug causes the compile ######         module M : sig - ######   end +######         end - ######   end +###### end -######   module M' : sig ... - ######   end +###### module M' : sig ... +###### end -######   module type S7 = sig +###### module type S7 = sig ######         type t @@ -217,12 +217,12 @@ The module needs at least one signature item, otherwise a bug causes the compile - ######   end +###### end -######   module type S8 = sig +###### module type S8 = sig ######         type t @@ -244,55 +244,55 @@ The module needs at least one signature item, otherwise a bug causes the compile - ######   end +###### end -######   module type S9 = sig +###### module type S9 = sig - ######   end +###### end -######   module Mutually : sig ... - ######   end +###### module Mutually : sig ... +###### end -######   module Recursive : sig ... - ######   end +###### module Recursive : sig ... +###### end ModuleS Module type `` Module.S `` -######   type t +###### type t -######   type u +###### type u -######   type 'a v +###### type 'a v -######   type ('a, 'b) w +###### type ('a, 'b) w -######   module M : sig +###### module M : sig - ######   end +###### end ModuleSM @@ -303,29 +303,29 @@ ModuleS3 Module type `` Module.S3 `` -######   type t = int +###### type t = int -######   type u = string +###### type u = string -######   type 'a v +###### type 'a v -######   type ('a, 'b) w +###### type ('a, 'b) w -######   module M : sig +###### module M : sig - ######   end +###### end ModuleS3M @@ -336,24 +336,24 @@ ModuleS4 Module type `` Module.S4 `` -######   type u +###### type u -######   type 'a v +###### type 'a v -######   type ('a, 'b) w +###### type ('a, 'b) w -######   module M : sig +###### module M : sig - ######   end +###### end ModuleS4M @@ -364,24 +364,24 @@ ModuleS5 Module type `` Module.S5 `` -######   type t +###### type t -######   type u +###### type u -######   type ('a, 'b) w +###### type ('a, 'b) w -######   module M : sig +###### module M : sig - ######   end +###### end ModuleS5M @@ -392,24 +392,24 @@ ModuleS6 Module type `` Module.S6 `` -######   type t +###### type t -######   type u +###### type u -######   type 'a v +###### type 'a v -######   module M : sig +###### module M : sig - ######   end +###### end ModuleS6M @@ -424,49 +424,49 @@ ModuleS7 Module type `` Module.S7 `` -######   type t +###### type t -######   type u +###### type u -######   type 'a v +###### type 'a v -######   type ('a, 'b) w +###### type ('a, 'b) w -######   module M = M' +###### module M = M' ModuleS8 Module type `` Module.S8 `` -######   type t +###### type t -######   type u +###### type u -######   type 'a v +###### type 'a v -######   type ('a, 'b) w +###### type ('a, 'b) w ModuleS9 diff --git a/test/generators/markdown/Module_type_alias.md b/test/generators/markdown/Module_type_alias.md index ab9dd3a7b6..3d729567b1 100644 --- a/test/generators/markdown/Module_type_alias.md +++ b/test/generators/markdown/Module_type_alias.md @@ -6,19 +6,19 @@ Module_type_alias Module Type Aliases -######   module type A = sig +###### module type A = sig ######         type a - ######   end +###### end -######   module type B = sig +###### module type B = sig ## Parameters @@ -29,11 +29,11 @@ Module Type Aliases ######         module C : sig -######                                 type c +######                 type c - ######   end +######         end @@ -47,17 +47,17 @@ Module Type Aliases - ######   end +###### end -######   module type D = A +###### module type D = A -######   module type E = sig +###### module type E = sig ## Parameters @@ -68,11 +68,11 @@ Module Type Aliases ######         module F : sig -######                                 type f +######                 type f - ######   end +######         end @@ -80,11 +80,11 @@ Module Type Aliases ######         module C : sig -######                                 type c +######                 type c - ######   end +######         end @@ -98,12 +98,12 @@ Module Type Aliases - ######   end +###### end -######   module type G = sig +###### module type G = sig ## Parameters @@ -114,11 +114,11 @@ Module Type Aliases ######         module H : sig -######                                 type h +######                 type h - ######   end +######         end @@ -132,138 +132,138 @@ Module Type Aliases - ######   end +###### end -######   module type I = B +###### module type I = B Module_type_aliasA Module type `` Module_type_alias.A `` -######   type a +###### type a Module_type_aliasB Module type `` Module_type_alias.B `` -# Parameters +#:parameters Parameters -######   module C : sig +###### module C : sig ######         type c - ######   end +###### end -# Signature +#:signature Signature -######   type b +###### type b Module_type_aliasB1-C Parameter `` B.1-C `` -######   type c +###### type c Module_type_aliasE Module type `` Module_type_alias.E `` -# Parameters +#:parameters Parameters -######   module F : sig +###### module F : sig ######         type f - ######   end +###### end -######   module C : sig +###### module C : sig ######         type c - ######   end +###### end -# Signature +#:signature Signature -######   type b +###### type b Module_type_aliasE1-F Parameter `` E.1-F `` -######   type f +###### type f Module_type_aliasE1-C Parameter `` E.1-C `` -######   type c +###### type c Module_type_aliasG Module type `` Module_type_alias.G `` -# Parameters +#:parameters Parameters -######   module H : sig +###### module H : sig ######         type h - ######   end +###### end -# Signature +#:signature Signature -######   type a +###### type a Module_type_aliasG1-H Parameter `` G.1-H `` -######   type h +###### type h diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md index 502734d9ad..5bc31380c1 100644 --- a/test/generators/markdown/Nested.F.md +++ b/test/generators/markdown/Nested.F.md @@ -10,15 +10,15 @@ This is a functor F. Some additional comments. -# Type +#:type Type -# Parameters +#:parameters Parameters -######   module Arg1 : sig +###### module Arg1 : sig ### Type @@ -46,12 +46,12 @@ The value of y. - ######   end +###### end -######   module Arg2 : sig +###### module Arg2 : sig ### Type @@ -66,16 +66,16 @@ Some type. - ######   end +###### end -# Signature +#:signature Signature -######   type t = Arg1.t * Arg2.t +###### type t = Arg1.t * Arg2.t Some type. @@ -85,11 +85,11 @@ NestedF1-Arg1 Parameter `` F.1-Arg1 `` -# Type +#:type Type -######   type t +###### type t Some type. @@ -97,11 +97,11 @@ Some type. -# Values +#:values Values -######   val y : t +###### val y : t The value of y. @@ -111,11 +111,11 @@ NestedF2-Arg2 Parameter `` F.2-Arg2 `` -# Type +#:type Type -######   type t +###### type t Some type. diff --git a/test/generators/markdown/Nested.X.md b/test/generators/markdown/Nested.X.md index 3aad03feaf..a53aecfe72 100644 --- a/test/generators/markdown/Nested.X.md +++ b/test/generators/markdown/Nested.X.md @@ -10,11 +10,11 @@ This is module X. Some additional comments. -# Type +#:type Type -######   type t +###### type t Some type. @@ -22,11 +22,11 @@ Some type. -# Values +#:values Values -######   val x : t +###### val x : t The value of x. diff --git a/test/generators/markdown/Nested.inherits.md b/test/generators/markdown/Nested.inherits.md index 7edb7aecfb..19627332b3 100644 --- a/test/generators/markdown/Nested.inherits.md +++ b/test/generators/markdown/Nested.inherits.md @@ -2,5 +2,5 @@ Nestedinherits Class `` Nested.inherits `` -######   inherit z +###### inherit z diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md index a527e866a6..d8b0069f03 100644 --- a/test/generators/markdown/Nested.md +++ b/test/generators/markdown/Nested.md @@ -6,12 +6,12 @@ Nested This comment needs to be here before #235 is fixed. -# Module +#:module Module -######   module X : sig ... - ######   end +###### module X : sig ... +###### end This is module X. @@ -19,11 +19,11 @@ This is module X. -# Module type +#:module-type Module type -######   module type Y = sig +###### module type Y = sig ### Type @@ -51,7 +51,7 @@ The value of y. - ######   end +###### end This is module type Y. @@ -59,13 +59,13 @@ This is module type Y. -# Functor +#:functor Functor -######   module F (Arg1 : Y) (Arg2 : sig ... - ######   end) : sig ... - ######   end +###### module F (Arg1 : Y) (Arg2 : sig ... +###### end) : sig ... +###### end This is a functor F. @@ -73,12 +73,12 @@ This is a functor F. -# Class +#:class Class -######   class virtual z : object ... - ######   end +###### class virtual z : object ... +###### end This is class z. @@ -86,8 +86,8 @@ This is class z. -######   class virtual inherits : object ... - ######   end +###### class virtual inherits : object ... +###### end NestedX @@ -102,11 +102,11 @@ This is module X. Some additional comments. -# Type +#:type Type -######   type t +###### type t Some type. @@ -114,11 +114,11 @@ Some type. -# Values +#:values Values -######   val x : t +###### val x : t The value of x. @@ -136,11 +136,11 @@ This is module type Y. Some additional comments. -# Type +#:type Type -######   type t +###### type t Some type. @@ -148,11 +148,11 @@ Some type. -# Values +#:values Values -######   val y : t +###### val y : t The value of y. @@ -170,15 +170,15 @@ This is a functor F. Some additional comments. -# Type +#:type Type -# Parameters +#:parameters Parameters -######   module Arg1 : sig +###### module Arg1 : sig ### Type @@ -206,12 +206,12 @@ The value of y. - ######   end +###### end -######   module Arg2 : sig +###### module Arg2 : sig ### Type @@ -226,16 +226,16 @@ Some type. - ######   end +###### end -# Signature +#:signature Signature -######   type t = Arg1.t * Arg2.t +###### type t = Arg1.t * Arg2.t Some type. @@ -245,11 +245,11 @@ NestedF1-Arg1 Parameter `` F.1-Arg1 `` -# Type +#:type Type -######   type t +###### type t Some type. @@ -257,11 +257,11 @@ Some type. -# Values +#:values Values -######   val y : t +###### val y : t The value of y. @@ -271,11 +271,11 @@ NestedF2-Arg2 Parameter `` F.2-Arg2 `` -# Type +#:type Type -######   type t +###### type t Some type. @@ -293,7 +293,7 @@ This is class z. Some additional comments. -######   val y : int +###### val y : int Some value. @@ -301,16 +301,16 @@ Some value. -######   val mutable virtual y' : int +###### val mutable virtual y' : int -# Methods +#:methods Methods -######   method z : int +###### method z : int Some method. @@ -318,12 +318,12 @@ Some method. -######   method private virtual z' : int +###### method private virtual z' : int Nestedinherits Class `` Nested.inherits `` -######   inherit z +###### inherit z diff --git a/test/generators/markdown/Nested.z.md b/test/generators/markdown/Nested.z.md index 4e5bb509c9..e11c1aef1e 100644 --- a/test/generators/markdown/Nested.z.md +++ b/test/generators/markdown/Nested.z.md @@ -10,7 +10,7 @@ This is class z. Some additional comments. -######   val y : int +###### val y : int Some value. @@ -18,16 +18,16 @@ Some value. -######   val mutable virtual y' : int +###### val mutable virtual y' : int -# Methods +#:methods Methods -######   method z : int +###### method z : int Some method. @@ -35,5 +35,5 @@ Some method. -######   method private virtual z' : int +###### method private virtual z' : int diff --git a/test/generators/markdown/Ocamlary.Aliases.E.md b/test/generators/markdown/Ocamlary.Aliases.E.md index 6346c1f37e..51d13a6215 100644 --- a/test/generators/markdown/Ocamlary.Aliases.E.md +++ b/test/generators/markdown/Ocamlary.Aliases.E.md @@ -2,10 +2,10 @@ OcamlaryAliasesE Module `` Aliases.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.A.md b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md index baa1f5d98f..e48e51f985 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.A.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md @@ -2,10 +2,10 @@ OcamlaryAliasesFooA Module `` Foo.A `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.B.md b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md index f704a3a1fd..dbde19bc21 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.B.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md @@ -2,10 +2,10 @@ OcamlaryAliasesFooB Module `` Foo.B `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.C.md b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md index b5e2a498c7..7a028733a6 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.C.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md @@ -2,10 +2,10 @@ OcamlaryAliasesFooC Module `` Foo.C `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.D.md b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md index b8d401c4a2..a5516458ca 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.D.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md @@ -2,10 +2,10 @@ OcamlaryAliasesFooD Module `` Foo.D `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.E.md b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md index e5d5c8cf66..d824103704 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.E.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md @@ -2,10 +2,10 @@ OcamlaryAliasesFooE Module `` Foo.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.md b/test/generators/markdown/Ocamlary.Aliases.Foo.md index 22ed4ae630..24f9ee0604 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.md @@ -2,90 +2,90 @@ OcamlaryAliasesFoo Module `` Aliases.Foo `` -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B : sig ... - ######   end +###### module B : sig ... +###### end -######   module C : sig ... - ######   end +###### module C : sig ... +###### end -######   module D : sig ... - ######   end +###### module D : sig ... +###### end -######   module E : sig ... - ######   end +###### module E : sig ... +###### end OcamlaryAliasesFooA Module `` Foo.A `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooB Module `` Foo.B `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooC Module `` Foo.C `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooD Module `` Foo.D `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooE Module `` Foo.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.Y.md b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md index fb09bdeba7..07002b992b 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P1.Y.md +++ b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md @@ -2,10 +2,10 @@ OcamlaryAliasesP1Y Module `` P1.Y `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.md b/test/generators/markdown/Ocamlary.Aliases.P1.md index 9cf1af5639..cedfb0fa98 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P1.md +++ b/test/generators/markdown/Ocamlary.Aliases.P1.md @@ -2,18 +2,18 @@ OcamlaryAliasesP1 Module `` Aliases.P1 `` -######   module Y : sig ... - ######   end +###### module Y : sig ... +###### end OcamlaryAliasesP1Y Module `` P1.Y `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t diff --git a/test/generators/markdown/Ocamlary.Aliases.P2.md b/test/generators/markdown/Ocamlary.Aliases.P2.md index da7c1cf012..4f504c2166 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P2.md +++ b/test/generators/markdown/Ocamlary.Aliases.P2.md @@ -2,5 +2,5 @@ OcamlaryAliasesP2 Module `` Aliases.P2 `` -######   module Z = Z +###### module Z = Z diff --git a/test/generators/markdown/Ocamlary.Aliases.Std.md b/test/generators/markdown/Ocamlary.Aliases.Std.md index bd7913f3bc..6437bb9df0 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Std.md +++ b/test/generators/markdown/Ocamlary.Aliases.Std.md @@ -2,25 +2,25 @@ OcamlaryAliasesStd Module `` Aliases.Std `` -######   module A = Foo.A +###### module A = Foo.A -######   module B = Foo.B +###### module B = Foo.B -######   module C = Foo.C +###### module C = Foo.C -######   module D = Foo.D +###### module D = Foo.D -######   module E = Foo.E +###### module E = Foo.E diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index dc64b2ace9..b7dff3c3ba 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -6,49 +6,49 @@ OcamlaryAliases Let's imitate jst's layout. -######   module Foo : sig ... - ######   end +###### module Foo : sig ... +###### end -######   module A' = Foo.A +###### module A' = Foo.A -######   type tata = Foo.A.t +###### type tata = Foo.A.t -######   type tbtb = Foo.B.t +###### type tbtb = Foo.B.t -######   type tete +###### type tete -######   type tata' = A'.t +###### type tata' = A'.t -######   type tete2 = Foo.E.t +###### type tete2 = Foo.E.t -######   module Std : sig ... - ######   end +###### module Std : sig ... +###### end -######   type stde = Std.E.t +###### type stde = Std.E.t @@ -62,33 +62,33 @@ Just for giggle, let's see what happens when we include `` Foo `` . -######   module A = Foo.A +###### module A = Foo.A -######   module B = Foo.B +###### module B = Foo.B -######   module C = Foo.C +###### module C = Foo.C -######   module D = Foo.D +###### module D = Foo.D -######   module E : sig ... - ######   end +###### module E : sig ... +###### end -######   type testa = A.t +###### type testa = A.t @@ -97,190 +97,190 @@ And also, let's refer to `` A.t `` and `` Foo.B.id `` -######   module P1 : sig ... - ######   end +###### module P1 : sig ... +###### end -######   module P2 : sig ... - ######   end +###### module P2 : sig ... +###### end -######   module X1 = P2.Z +###### module X1 = P2.Z -######   module X2 = P2.Z +###### module X2 = P2.Z -######   type p1 = X1.t +###### type p1 = X1.t -######   type p2 = X2.t +###### type p2 = X2.t OcamlaryAliasesFoo Module `` Aliases.Foo `` -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B : sig ... - ######   end +###### module B : sig ... +###### end -######   module C : sig ... - ######   end +###### module C : sig ... +###### end -######   module D : sig ... - ######   end +###### module D : sig ... +###### end -######   module E : sig ... - ######   end +###### module E : sig ... +###### end OcamlaryAliasesFooA Module `` Foo.A `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooB Module `` Foo.B `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooC Module `` Foo.C `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooD Module `` Foo.D `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooE Module `` Foo.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesStd Module `` Aliases.Std `` -######   module A = Foo.A +###### module A = Foo.A -######   module B = Foo.B +###### module B = Foo.B -######   module C = Foo.C +###### module C = Foo.C -######   module D = Foo.D +###### module D = Foo.D -######   module E = Foo.E +###### module E = Foo.E OcamlaryAliasesE Module `` Aliases.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesP1 Module `` Aliases.P1 `` -######   module Y : sig ... - ######   end +###### module Y : sig ... +###### end OcamlaryAliasesP1Y Module `` P1.Y `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesP2 Module `` Aliases.P2 `` -######   module Z = Z +###### module Z = Z diff --git a/test/generators/markdown/Ocamlary.Buffer.md b/test/generators/markdown/Ocamlary.Buffer.md index 8e1af092bf..cec343418f 100644 --- a/test/generators/markdown/Ocamlary.Buffer.md +++ b/test/generators/markdown/Ocamlary.Buffer.md @@ -6,5 +6,5 @@ OcamlaryBuffer `` Buffer `` .t -######   val f : Stdlib.Buffer.t -> unit +###### val f : Stdlib.Buffer.t -> unit diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md index 0340c0cd7d..5cbef3223e 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md @@ -2,10 +2,10 @@ OcamlaryCanonicalTestBaseList Module `` Base.List `` -######   type 'a t +###### type 'a t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md index 58f8d59c18..c76328c7b7 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md @@ -2,18 +2,18 @@ OcamlaryCanonicalTestBase Module `` CanonicalTest.Base `` -######   module List : sig ... - ######   end +###### module List : sig ... +###### end OcamlaryCanonicalTestBaseList Module `` Base.List `` -######   type 'a t +###### type 'a t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md index 98b3b7fade..6d06f32975 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md @@ -2,10 +2,10 @@ OcamlaryCanonicalTestList_modif Module `` CanonicalTest.List_modif `` -######   type 'c t = 'c Base.List.t +###### type 'c t = 'c Base.List.t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.md b/test/generators/markdown/Ocamlary.CanonicalTest.md index 980e5a45cc..4bf5769ad5 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.md @@ -2,43 +2,43 @@ OcamlaryCanonicalTest Module `` Ocamlary.CanonicalTest `` -######   module Base : sig ... - ######   end +###### module Base : sig ... +###### end -######   module List_modif : module type of Base.List with type 'c t = 'c Base.List.t +###### module List_modif : module type of Base.List with type 'c t = 'c Base.List.t OcamlaryCanonicalTestBase Module `` CanonicalTest.Base `` -######   module List : sig ... - ######   end +###### module List : sig ... +###### end OcamlaryCanonicalTestBaseList Module `` Base.List `` -######   type 'a t +###### type 'a t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t OcamlaryCanonicalTestList_modif Module `` CanonicalTest.List_modif `` -######   type 'c t = 'c Base.List.t +###### type 'c t = 'c Base.List.t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md index 8ea39b3681..f6dd67f7b3 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md @@ -6,7 +6,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index 271b15bfaf..b9e12780fc 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -6,7 +6,7 @@ OcamlaryCollectionModuleInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -14,8 +14,8 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig ... - ######   end +###### module InnerModuleA' : sig ... +###### end This comment is for `` InnerModuleA' `` . @@ -23,7 +23,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -33,7 +33,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -47,7 +47,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -61,7 +61,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md index a226843df6..d3ff2e3739 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.md @@ -6,7 +6,7 @@ OcamlaryCollectionModule This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -14,13 +14,13 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig ... - ######   end +###### module InnerModuleA : sig ... +###### end This comment is for `` InnerModuleA `` . @@ -28,7 +28,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -42,7 +42,7 @@ OcamlaryCollectionModuleInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -50,8 +50,8 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig ... - ######   end +###### module InnerModuleA' : sig ... +###### end This comment is for `` InnerModuleA' `` . @@ -59,7 +59,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -69,7 +69,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -83,7 +83,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -97,7 +97,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md index f98507df4a..4f8cc16e0e 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md @@ -2,5 +2,5 @@ OcamlaryDep1XYc Class `` Y.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.md index 0c2f851570..9f125430c2 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md @@ -2,13 +2,13 @@ OcamlaryDep1XY Module `` X.Y `` -######   class c : object ... - ######   end +###### class c : object ... +###### end OcamlaryDep1XYc Class `` Y.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep1.X.md b/test/generators/markdown/Ocamlary.Dep1.X.md index 406e458d49..f3980facfe 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.md @@ -2,20 +2,20 @@ OcamlaryDep1X Module `` Dep1.X `` -######   module Y : S +###### module Y : S OcamlaryDep1XY Module `` X.Y `` -######   class c : object ... - ######   end +###### class c : object ... +###### end OcamlaryDep1XYc Class `` Y.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep1.md b/test/generators/markdown/Ocamlary.Dep1.md index 15670af754..a078fff6a9 100644 --- a/test/generators/markdown/Ocamlary.Dep1.md +++ b/test/generators/markdown/Ocamlary.Dep1.md @@ -2,68 +2,68 @@ OcamlaryDep1 Module `` Ocamlary.Dep1 `` -######   module type S = sig +###### module type S = sig ######         class c : object -######                                 method m : int +######                 method m : int - ######   end +######         end - ######   end +###### end -######   module X : sig ... - ######   end +###### module X : sig ... +###### end OcamlaryDep1S Module type `` Dep1.S `` -######   class c : object +###### class c : object ######         method m : int - ######   end +###### end OcamlaryDep1Sc Class `` S.c `` -######   method m : int +###### method m : int OcamlaryDep1X Module `` Dep1.X `` -######   module Y : S +###### module Y : S OcamlaryDep1XY Module `` X.Y `` -######   class c : object ... - ######   end +###### class c : object ... +###### end OcamlaryDep1XYc Class `` Y.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep11.md b/test/generators/markdown/Ocamlary.Dep11.md index a91b4d1f99..a8e589f685 100644 --- a/test/generators/markdown/Ocamlary.Dep11.md +++ b/test/generators/markdown/Ocamlary.Dep11.md @@ -2,40 +2,40 @@ OcamlaryDep11 Module `` Ocamlary.Dep11 `` -######   module type S = sig +###### module type S = sig ######         class c : object -######                                 method m : int +######                 method m : int - ######   end +######         end - ######   end +###### end OcamlaryDep11S Module type `` Dep11.S `` -######   class c : object +###### class c : object ######         method m : int - ######   end +###### end OcamlaryDep11Sc Class `` S.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep12.md b/test/generators/markdown/Ocamlary.Dep12.md index 489a2114c0..799fd67e88 100644 --- a/test/generators/markdown/Ocamlary.Dep12.md +++ b/test/generators/markdown/Ocamlary.Dep12.md @@ -2,32 +2,32 @@ OcamlaryDep12 Module `` Ocamlary.Dep12 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type S - ######   end +###### end -# Signature +#:signature Signature -######   module type T = Arg.S +###### module type T = Arg.S OcamlaryDep121-Arg Parameter `` Dep12.1-Arg `` -######   module type S +###### module type S diff --git a/test/generators/markdown/Ocamlary.Dep13.c.md b/test/generators/markdown/Ocamlary.Dep13.c.md index 77a2852320..94018aab7c 100644 --- a/test/generators/markdown/Ocamlary.Dep13.c.md +++ b/test/generators/markdown/Ocamlary.Dep13.c.md @@ -2,5 +2,5 @@ OcamlaryDep13c Class `` Dep13.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep13.md b/test/generators/markdown/Ocamlary.Dep13.md index 8d172f1851..457ce6dec6 100644 --- a/test/generators/markdown/Ocamlary.Dep13.md +++ b/test/generators/markdown/Ocamlary.Dep13.md @@ -2,13 +2,13 @@ OcamlaryDep13 Module `` Ocamlary.Dep13 `` -######   class c : object ... - ######   end +###### class c : object ... +###### end OcamlaryDep13c Class `` Dep13.c `` -######   method m : int +###### method m : int diff --git a/test/generators/markdown/Ocamlary.Dep2.A.md b/test/generators/markdown/Ocamlary.Dep2.A.md index 61fdce33ef..19626b1622 100644 --- a/test/generators/markdown/Ocamlary.Dep2.A.md +++ b/test/generators/markdown/Ocamlary.Dep2.A.md @@ -2,5 +2,5 @@ OcamlaryDep2A Module `` Dep2.A `` -######   module Y : Arg.S +###### module Y : Arg.S diff --git a/test/generators/markdown/Ocamlary.Dep2.md b/test/generators/markdown/Ocamlary.Dep2.md index 6aed75586a..0f310ddc8f 100644 --- a/test/generators/markdown/Ocamlary.Dep2.md +++ b/test/generators/markdown/Ocamlary.Dep2.md @@ -2,11 +2,11 @@ OcamlaryDep2 Module `` Ocamlary.Dep2 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type S @@ -17,61 +17,61 @@ OcamlaryDep2 ######         module X : sig -######                                 module Y : S +######                 module Y : S - ######   end +######         end - ######   end +###### end -# Signature +#:signature Signature -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B = A.Y +###### module B = A.Y OcamlaryDep21-Arg Parameter `` Dep2.1-Arg `` -######   module type S +###### module type S -######   module X : sig +###### module X : sig ######         module Y : S - ######   end +###### end OcamlaryDep21-ArgX Module `` 1-Arg.X `` -######   module Y : S +###### module Y : S OcamlaryDep2A Module `` Dep2.A `` -######   module Y : Arg.S +###### module Y : Arg.S diff --git a/test/generators/markdown/Ocamlary.Dep3.md b/test/generators/markdown/Ocamlary.Dep3.md index b52906f953..2ffba59dce 100644 --- a/test/generators/markdown/Ocamlary.Dep3.md +++ b/test/generators/markdown/Ocamlary.Dep3.md @@ -2,5 +2,5 @@ OcamlaryDep3 Module `` Ocamlary.Dep3 `` -######   type a +###### type a diff --git a/test/generators/markdown/Ocamlary.Dep4.X.md b/test/generators/markdown/Ocamlary.Dep4.X.md index 68dd72c33c..a657ce711f 100644 --- a/test/generators/markdown/Ocamlary.Dep4.X.md +++ b/test/generators/markdown/Ocamlary.Dep4.X.md @@ -2,5 +2,5 @@ OcamlaryDep4X Module `` Dep4.X `` -######   type b +###### type b diff --git a/test/generators/markdown/Ocamlary.Dep4.md b/test/generators/markdown/Ocamlary.Dep4.md index 0d20d865b5..4b861944ba 100644 --- a/test/generators/markdown/Ocamlary.Dep4.md +++ b/test/generators/markdown/Ocamlary.Dep4.md @@ -2,80 +2,80 @@ OcamlaryDep4 Module `` Ocamlary.Dep4 `` -######   module type T = sig +###### module type T = sig ######         type b - ######   end +###### end -######   module type S = sig +###### module type S = sig ######         module X : sig -######                                 type b +######                 type b - ######   end +######         end ######         module Y : sig - ######   end +######         end - ######   end +###### end -######   module X : T +###### module X : T OcamlaryDep4T Module type `` Dep4.T `` -######   type b +###### type b OcamlaryDep4S Module type `` Dep4.S `` -######   module X : sig +###### module X : sig ######         type b - ######   end +###### end -######   module Y : sig +###### module Y : sig - ######   end +###### end OcamlaryDep4SX Module `` S.X `` -######   type b +###### type b OcamlaryDep4SY @@ -86,5 +86,5 @@ OcamlaryDep4X Module `` Dep4.X `` -######   type b +###### type b diff --git a/test/generators/markdown/Ocamlary.Dep5.Z.md b/test/generators/markdown/Ocamlary.Dep5.Z.md index 9cc4e98f10..71159b85c9 100644 --- a/test/generators/markdown/Ocamlary.Dep5.Z.md +++ b/test/generators/markdown/Ocamlary.Dep5.Z.md @@ -2,10 +2,10 @@ OcamlaryDep5Z Module `` Dep5.Z `` -######   module X : Arg.T +###### module X : Arg.T -######   module Y = Dep3 +###### module Y = Dep3 diff --git a/test/generators/markdown/Ocamlary.Dep5.md b/test/generators/markdown/Ocamlary.Dep5.md index 4906e50bd9..01ab8aa06e 100644 --- a/test/generators/markdown/Ocamlary.Dep5.md +++ b/test/generators/markdown/Ocamlary.Dep5.md @@ -2,11 +2,11 @@ OcamlaryDep5 Module `` Ocamlary.Dep5 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type T @@ -17,18 +17,18 @@ OcamlaryDep5 ######         module type S = sig -######                                 module X : T +######                 module X : T -######                                 module Y : sig +######                 module Y : sig - ######   end +######                 end - ######   end +######         end @@ -37,28 +37,28 @@ OcamlaryDep5 - ######   end +###### end -# Signature +#:signature Signature -######   module Z : Arg.S with module Y = Dep3 +###### module Z : Arg.S with module Y = Dep3 OcamlaryDep51-Arg Parameter `` Dep5.1-Arg `` -######   module type T +###### module type T -######   module type S = sig +###### module type S = sig ######         module X : T @@ -68,30 +68,30 @@ OcamlaryDep51-Arg ######         module Y : sig - ######   end +######         end - ######   end +###### end -######   module X : T +###### module X : T OcamlaryDep51-ArgS Module type `` 1-Arg.S `` -######   module X : T +###### module X : T -######   module Y : sig +###### module Y : sig - ######   end +###### end OcamlaryDep51-ArgSY @@ -102,10 +102,10 @@ OcamlaryDep5Z Module `` Dep5.Z `` -######   module X : Arg.T +###### module X : Arg.T -######   module Y = Dep3 +###### module Y = Dep3 diff --git a/test/generators/markdown/Ocamlary.Dep6.X.Y.md b/test/generators/markdown/Ocamlary.Dep6.X.Y.md index 020b5d00c3..5598788ae5 100644 --- a/test/generators/markdown/Ocamlary.Dep6.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep6.X.Y.md @@ -2,5 +2,5 @@ OcamlaryDep6XY Module `` X.Y `` -######   type d +###### type d diff --git a/test/generators/markdown/Ocamlary.Dep6.X.md b/test/generators/markdown/Ocamlary.Dep6.X.md index dc42673d86..d6f5174ab9 100644 --- a/test/generators/markdown/Ocamlary.Dep6.X.md +++ b/test/generators/markdown/Ocamlary.Dep6.X.md @@ -2,17 +2,17 @@ OcamlaryDep6X Module `` Dep6.X `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep6XY Module `` X.Y `` -######   type d +###### type d diff --git a/test/generators/markdown/Ocamlary.Dep6.md b/test/generators/markdown/Ocamlary.Dep6.md index 6d7088cde8..0c49a9fbcd 100644 --- a/test/generators/markdown/Ocamlary.Dep6.md +++ b/test/generators/markdown/Ocamlary.Dep6.md @@ -2,19 +2,19 @@ OcamlaryDep6 Module `` Ocamlary.Dep6 `` -######   module type S = sig +###### module type S = sig ######         type d - ######   end +###### end -######   module type T = sig +###### module type T = sig ######         module type R = S @@ -25,70 +25,70 @@ OcamlaryDep6 ######         module Y : sig -######                                 type d +######                 type d - ######   end +######         end - ######   end +###### end -######   module X : T +###### module X : T OcamlaryDep6S Module type `` Dep6.S `` -######   type d +###### type d OcamlaryDep6T Module type `` Dep6.T `` -######   module type R = S +###### module type R = S -######   module Y : sig +###### module Y : sig ######         type d - ######   end +###### end OcamlaryDep6TY Module `` T.Y `` -######   type d +###### type d OcamlaryDep6X Module `` Dep6.X `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep6XY Module `` X.Y `` -######   type d +###### type d diff --git a/test/generators/markdown/Ocamlary.Dep7.M.md b/test/generators/markdown/Ocamlary.Dep7.M.md index 06cc441831..e49bbefd5d 100644 --- a/test/generators/markdown/Ocamlary.Dep7.M.md +++ b/test/generators/markdown/Ocamlary.Dep7.M.md @@ -2,10 +2,10 @@ OcamlaryDep7M Module `` Dep7.M `` -######   module type R = Arg.S +###### module type R = Arg.S -######   module Y : R +###### module Y : R diff --git a/test/generators/markdown/Ocamlary.Dep7.md b/test/generators/markdown/Ocamlary.Dep7.md index 9e979ac960..5b68d8eb27 100644 --- a/test/generators/markdown/Ocamlary.Dep7.md +++ b/test/generators/markdown/Ocamlary.Dep7.md @@ -2,11 +2,11 @@ OcamlaryDep7 Module `` Ocamlary.Dep7 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type S @@ -17,16 +17,16 @@ OcamlaryDep7 ######         module type T = sig -######                                 module type R = S +######                 module type R = S -######                                 module Y : R +######                 module Y : R - ######   end +######         end @@ -34,41 +34,41 @@ OcamlaryDep7 ######         module X : sig -######                                 module type R = S +######                 module type R = S -######                                 module Y : R +######                 module Y : R - ######   end +######         end - ######   end +###### end -# Signature +#:signature Signature -######   module M : Arg.T +###### module M : Arg.T OcamlaryDep71-Arg Parameter `` Dep7.1-Arg `` -######   module type S +###### module type S -######   module type T = sig +###### module type T = sig ######         module type R = S @@ -80,12 +80,12 @@ OcamlaryDep71-Arg - ######   end +###### end -######   module X : sig +###### module X : sig ######         module type R = S @@ -97,41 +97,41 @@ OcamlaryDep71-Arg - ######   end +###### end OcamlaryDep71-ArgT Module type `` 1-Arg.T `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep71-ArgX Module `` 1-Arg.X `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep7M Module `` Dep7.M `` -######   module type R = Arg.S +###### module type R = Arg.S -######   module Y : R +###### module Y : R diff --git a/test/generators/markdown/Ocamlary.Dep8.md b/test/generators/markdown/Ocamlary.Dep8.md index 2ab89241b1..b960e6f945 100644 --- a/test/generators/markdown/Ocamlary.Dep8.md +++ b/test/generators/markdown/Ocamlary.Dep8.md @@ -2,19 +2,19 @@ OcamlaryDep8 Module `` Ocamlary.Dep8 `` -######   module type T = sig +###### module type T = sig ######         type t - ######   end +###### end OcamlaryDep8T Module type `` Dep8.T `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.Dep9.md b/test/generators/markdown/Ocamlary.Dep9.md index d61ffc7dfc..4e4b785070 100644 --- a/test/generators/markdown/Ocamlary.Dep9.md +++ b/test/generators/markdown/Ocamlary.Dep9.md @@ -2,32 +2,32 @@ OcamlaryDep9 Module `` Ocamlary.Dep9 `` -# Parameters +#:parameters Parameters -######   module X : sig +###### module X : sig ######         module type T - ######   end +###### end -# Signature +#:signature Signature -######   module type T = X.T +###### module type T = X.T OcamlaryDep91-X Parameter `` Dep9.1-X `` -######   module type T +###### module type T diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md index 29491b32b5..c5231d2145 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md @@ -2,5 +2,5 @@ OcamlaryDoubleInclude1DoubleInclude2 Module `` DoubleInclude1.DoubleInclude2 `` -######   type double_include +###### type double_include diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.md b/test/generators/markdown/Ocamlary.DoubleInclude1.md index e4537f1234..c490cd110d 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude1.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.md @@ -2,13 +2,13 @@ OcamlaryDoubleInclude1 Module `` Ocamlary.DoubleInclude1 `` -######   module DoubleInclude2 : sig ... - ######   end +###### module DoubleInclude2 : sig ... +###### end OcamlaryDoubleInclude1DoubleInclude2 Module `` DoubleInclude1.DoubleInclude2 `` -######   type double_include +###### type double_include diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md index 5558c75939..da84ee5184 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md @@ -2,5 +2,5 @@ OcamlaryDoubleInclude3DoubleInclude2 Module `` DoubleInclude3.DoubleInclude2 `` -######   type double_include +###### type double_include diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.md b/test/generators/markdown/Ocamlary.DoubleInclude3.md index ef26727621..21f040253b 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude3.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.md @@ -2,13 +2,13 @@ OcamlaryDoubleInclude3 Module `` Ocamlary.DoubleInclude3 `` -######   module DoubleInclude2 : sig ... - ######   end +###### module DoubleInclude2 : sig ... +###### end OcamlaryDoubleInclude3DoubleInclude2 Module `` DoubleInclude3.DoubleInclude2 `` -######   type double_include +###### type double_include diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md index 07e14423b5..9d457999ca 100644 --- a/test/generators/markdown/Ocamlary.ExtMod.md +++ b/test/generators/markdown/Ocamlary.ExtMod.md @@ -2,12 +2,12 @@ OcamlaryExtMod Module `` Ocamlary.ExtMod `` -######   type t = .. +###### type t = .. -######   type t += +###### type t += ######         | Leisureforce diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md index a94fe50080..600c3751b3 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md @@ -6,11 +6,11 @@ OcamlaryFunctorTypeOf This comment is for `` FunctorTypeOf `` . -# Parameters +#:parameters Parameters -######   module Collection : sig +###### module Collection : sig This comment is for `` CollectionModule `` . @@ -33,7 +33,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -41,17 +41,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -59,24 +59,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -91,16 +91,16 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end -# Signature +#:signature Signature -######   type t = Collection.collection +###### type t = Collection.collection This comment is for `` t `` . @@ -114,7 +114,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -122,12 +122,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -141,14 +141,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -159,21 +159,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -181,7 +181,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -195,7 +195,7 @@ OcamlaryFunctorTypeOf1-CollectionInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -203,7 +203,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -213,7 +213,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -221,7 +221,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -231,7 +231,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -245,7 +245,7 @@ OcamlaryFunctorTypeOf1-CollectionInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -259,7 +259,7 @@ OcamlaryFunctorTypeOf1-CollectionInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md index 92d951b843..56c508e394 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -2,19 +2,19 @@ OcamlaryIncludeInclude1 Module `` Ocamlary.IncludeInclude1 `` -######   module type IncludeInclude2 = sig +###### module type IncludeInclude2 = sig ######         type include_include - ######   end +###### end OcamlaryIncludeInclude1IncludeInclude2 Module type `` IncludeInclude1.IncludeInclude2 `` -######   type include_include +###### type include_include diff --git a/test/generators/markdown/Ocamlary.IncludedA.md b/test/generators/markdown/Ocamlary.IncludedA.md index 90983108fe..3938e55016 100644 --- a/test/generators/markdown/Ocamlary.IncludedA.md +++ b/test/generators/markdown/Ocamlary.IncludedA.md @@ -2,5 +2,5 @@ OcamlaryIncludedA Module `` Ocamlary.IncludedA `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.M.md b/test/generators/markdown/Ocamlary.M.md index 6f468c0d3c..153f8e1027 100644 --- a/test/generators/markdown/Ocamlary.M.md +++ b/test/generators/markdown/Ocamlary.M.md @@ -2,5 +2,5 @@ OcamlaryM Module `` Ocamlary.M `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.One.md b/test/generators/markdown/Ocamlary.One.md index 24e84a65af..c0904c85da 100644 --- a/test/generators/markdown/Ocamlary.One.md +++ b/test/generators/markdown/Ocamlary.One.md @@ -2,5 +2,5 @@ OcamlaryOne Module `` Ocamlary.One `` -######   type one +###### type one diff --git a/test/generators/markdown/Ocamlary.Only_a_module.md b/test/generators/markdown/Ocamlary.Only_a_module.md index e70b22d7ee..ebddf6aeaa 100644 --- a/test/generators/markdown/Ocamlary.Only_a_module.md +++ b/test/generators/markdown/Ocamlary.Only_a_module.md @@ -2,5 +2,5 @@ OcamlaryOnly_a_module Module `` Ocamlary.Only_a_module `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md index def421bdd0..f400467a1e 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md @@ -6,7 +6,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index eb7da99566..5860244ad5 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -6,7 +6,7 @@ OcamlaryRecollectionInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -14,8 +14,8 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig ... - ######   end +###### module InnerModuleA' : sig ... +###### end This comment is for `` InnerModuleA' `` . @@ -23,7 +23,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -33,7 +33,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -47,7 +47,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -61,7 +61,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md index d11cd945f8..71830d6315 100644 --- a/test/generators/markdown/Ocamlary.Recollection.md +++ b/test/generators/markdown/Ocamlary.Recollection.md @@ -2,11 +2,11 @@ OcamlaryRecollection Module `` Ocamlary.Recollection `` -# Parameters +#:parameters Parameters -######   module C : sig +###### module C : sig This comment is for `` CollectionModule `` . @@ -29,7 +29,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -37,17 +37,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -55,24 +55,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -87,12 +87,12 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end -# Signature +#:signature Signature This comment is for `` CollectionModule `` . @@ -100,7 +100,7 @@ This comment is for `` CollectionModule `` . -######   type collection = C.element list +###### type collection = C.element list This comment is for `` collection `` . @@ -108,13 +108,13 @@ This comment is for `` collection `` . -######   type element = C.collection +###### type element = C.collection -######   module InnerModuleA : sig ... - ######   end +###### module InnerModuleA : sig ... +###### end This comment is for `` InnerModuleA `` . @@ -122,7 +122,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -136,7 +136,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -144,12 +144,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -163,14 +163,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -181,21 +181,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -203,7 +203,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -217,7 +217,7 @@ OcamlaryRecollection1-CInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -225,7 +225,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -235,7 +235,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -243,7 +243,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -253,7 +253,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -267,7 +267,7 @@ OcamlaryRecollection1-CInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -281,7 +281,7 @@ OcamlaryRecollection1-CInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -295,7 +295,7 @@ OcamlaryRecollectionInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -303,8 +303,8 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig ... - ######   end +###### module InnerModuleA' : sig ... +###### end This comment is for `` InnerModuleA' `` . @@ -312,7 +312,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -322,7 +322,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -336,7 +336,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -350,7 +350,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . diff --git a/test/generators/markdown/Ocamlary.With10.md b/test/generators/markdown/Ocamlary.With10.md index 03eb2a2340..0434b4c14b 100644 --- a/test/generators/markdown/Ocamlary.With10.md +++ b/test/generators/markdown/Ocamlary.With10.md @@ -2,17 +2,17 @@ OcamlaryWith10 Module `` Ocamlary.With10 `` -######   module type T = sig +###### module type T = sig ######         module M : sig -######                                 module type S +######                 module type S - ######   end +######         end @@ -21,7 +21,7 @@ OcamlaryWith10 - ######   end +###### end `` With10.T `` is a submodule type. @@ -35,24 +35,24 @@ OcamlaryWith10T `` With10.T `` is a submodule type. -######   module M : sig +###### module M : sig ######         module type S - ######   end +###### end -######   module N : M.S +###### module N : M.S OcamlaryWith10TM Module `` T.M `` -######   module type S +###### module type S diff --git a/test/generators/markdown/Ocamlary.With2.md b/test/generators/markdown/Ocamlary.With2.md index fb45d93772..4d20406e37 100644 --- a/test/generators/markdown/Ocamlary.With2.md +++ b/test/generators/markdown/Ocamlary.With2.md @@ -2,19 +2,19 @@ OcamlaryWith2 Module `` Ocamlary.With2 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end OcamlaryWith2S Module type `` With2.S `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With3.N.md b/test/generators/markdown/Ocamlary.With3.N.md index 544b8da707..4e158f3f23 100644 --- a/test/generators/markdown/Ocamlary.With3.N.md +++ b/test/generators/markdown/Ocamlary.With3.N.md @@ -2,5 +2,5 @@ OcamlaryWith3N Module `` With3.N `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With3.md b/test/generators/markdown/Ocamlary.With3.md index 444f949552..f935e9c67a 100644 --- a/test/generators/markdown/Ocamlary.With3.md +++ b/test/generators/markdown/Ocamlary.With3.md @@ -2,17 +2,17 @@ OcamlaryWith3 Module `` Ocamlary.With3 `` -######   module M = With2 +###### module M = With2 -######   module N : M.S +###### module N : M.S OcamlaryWith3N Module `` With3.N `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With4.N.md b/test/generators/markdown/Ocamlary.With4.N.md index 5dfed34a4a..c246fe2cca 100644 --- a/test/generators/markdown/Ocamlary.With4.N.md +++ b/test/generators/markdown/Ocamlary.With4.N.md @@ -2,5 +2,5 @@ OcamlaryWith4N Module `` With4.N `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With4.md b/test/generators/markdown/Ocamlary.With4.md index 2a524eee68..a67668cbbb 100644 --- a/test/generators/markdown/Ocamlary.With4.md +++ b/test/generators/markdown/Ocamlary.With4.md @@ -2,12 +2,12 @@ OcamlaryWith4 Module `` Ocamlary.With4 `` -######   module N : With2.S +###### module N : With2.S OcamlaryWith4N Module `` With4.N `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With5.N.md b/test/generators/markdown/Ocamlary.With5.N.md index 1552b0bf37..21104a5d3e 100644 --- a/test/generators/markdown/Ocamlary.With5.N.md +++ b/test/generators/markdown/Ocamlary.With5.N.md @@ -2,5 +2,5 @@ OcamlaryWith5N Module `` With5.N `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With5.md b/test/generators/markdown/Ocamlary.With5.md index 9781a5ebe0..1d4fede806 100644 --- a/test/generators/markdown/Ocamlary.With5.md +++ b/test/generators/markdown/Ocamlary.With5.md @@ -2,31 +2,31 @@ OcamlaryWith5 Module `` Ocamlary.With5 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end -######   module N : S +###### module N : S OcamlaryWith5S Module type `` With5.S `` -######   type t +###### type t OcamlaryWith5N Module `` With5.N `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.With6.md b/test/generators/markdown/Ocamlary.With6.md index 5b968f0ac2..17b4c5921b 100644 --- a/test/generators/markdown/Ocamlary.With6.md +++ b/test/generators/markdown/Ocamlary.With6.md @@ -2,33 +2,33 @@ OcamlaryWith6 Module `` Ocamlary.With6 `` -######   module type T = sig +###### module type T = sig ######         module M : sig -######                                 module type S +######                 module type S -######                                 module N : S +######                 module N : S - ######   end +######         end - ######   end +###### end OcamlaryWith6T Module type `` With6.T `` -######   module M : sig +###### module M : sig ######         module type S @@ -40,17 +40,17 @@ OcamlaryWith6T - ######   end +###### end OcamlaryWith6TM Module `` T.M `` -######   module type S +###### module type S -######   module N : S +###### module N : S diff --git a/test/generators/markdown/Ocamlary.With7.md b/test/generators/markdown/Ocamlary.With7.md index 03376ecc10..f0a7b12fa8 100644 --- a/test/generators/markdown/Ocamlary.With7.md +++ b/test/generators/markdown/Ocamlary.With7.md @@ -2,32 +2,32 @@ OcamlaryWith7 Module `` Ocamlary.With7 `` -# Parameters +#:parameters Parameters -######   module X : sig +###### module X : sig ######         module type T - ######   end +###### end -# Signature +#:signature Signature -######   module type T = X.T +###### module type T = X.T OcamlaryWith71-X Parameter `` With7.1-X `` -######   module type T +###### module type T diff --git a/test/generators/markdown/Ocamlary.With9.md b/test/generators/markdown/Ocamlary.With9.md index 9a2731ea83..9167f360db 100644 --- a/test/generators/markdown/Ocamlary.With9.md +++ b/test/generators/markdown/Ocamlary.With9.md @@ -2,19 +2,19 @@ OcamlaryWith9 Module `` Ocamlary.With9 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end OcamlaryWith9S Module type `` With9.S `` -######   type t +###### type t diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 38034a585c..382e7cd5ba 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -55,12 +55,12 @@ You may find more information about this HTML documentation renderer at github.c This is some verbatim text: - verbatim + verbatim This is some verbatim text: - [][df[]]}} + [][df[]]}} Here is some raw LaTeX: @@ -103,7 +103,7 @@ An unassociated comment -# Level 1 +#:level-1 Level 1 @@ -127,8 +127,8 @@ An unassociated comment -######   module Empty : sig ... - ######   end +###### module Empty : sig ... +###### end A plain, empty module @@ -136,14 +136,14 @@ A plain, empty module -######   module type Empty = sig +###### module type Empty = sig ######         type t - ######   end +###### end An ambiguous, misnamed module type @@ -151,14 +151,14 @@ An ambiguous, misnamed module type -######   module type MissingComment = sig +###### module type MissingComment = sig ######         type t - ######   end +###### end An ambiguous, misnamed module type @@ -166,11 +166,11 @@ An ambiguous, misnamed module type -# Section 9000 +#:s9000 Section 9000 -######   module EmptyAlias = Empty +###### module EmptyAlias = Empty A plain module alias of `` Empty `` @@ -183,9 +183,9 @@ A plain module alias of `` Empty `` -######   module type EmptySig = sig +###### module type EmptySig = sig - ######   end +###### end A plain, empty module signature @@ -193,7 +193,7 @@ A plain, empty module signature -######   module type EmptySigAlias = EmptySig +###### module type EmptySigAlias = EmptySig A plain, empty module signature alias of @@ -201,7 +201,7 @@ A plain, empty module signature alias of -######   module ModuleWithSignature : EmptySig +###### module ModuleWithSignature : EmptySig A plain module of a signature of `` EmptySig `` (reference) @@ -209,7 +209,7 @@ A plain module of a signature of `` EmptySig `` (reference) -######   module ModuleWithSignatureAlias : EmptySigAlias +###### module ModuleWithSignatureAlias : EmptySigAlias A plain module with an alias signature @@ -217,29 +217,29 @@ A plain module with an alias signature -######   module One : sig ... - ######   end +###### module One : sig ... +###### end -######   module type SigForMod = sig +###### module type SigForMod = sig ######         module Inner : sig -######                                 module type Empty = sig +######                 module type Empty = sig - ######   end +######                 end - ######   end +######         end - ######   end +###### end There's a signature in a module in this signature. @@ -247,7 +247,7 @@ There's a signature in a module in this signature. -######   module type SuperSig = sig +###### module type SuperSig = sig ######         module type SubSigA = sig @@ -258,23 +258,23 @@ There's a signature in a module in this signature. -######                                 type t +######                 type t -######                                 module SubSigAMod : sig +######                 module SubSigAMod : sig -######                                                                                                                                 type sub_sig_a_mod +######                         type sub_sig_a_mod - ######   end +######                 end - ######   end +######         end @@ -287,11 +287,11 @@ There's a signature in a module in this signature. -######                                 type t +######                 type t - ######   end +######         end @@ -299,11 +299,11 @@ There's a signature in a module in this signature. ######         module type EmptySig = sig -######                                 type not_actually_empty +######                 type not_actually_empty - ######   end +######         end @@ -311,22 +311,22 @@ There's a signature in a module in this signature. ######         module type One = sig -######                                 type two +######                 type two - ######   end +######         end ######         module type SuperSig = sig - ######   end +######         end - ######   end +###### end @@ -335,8 +335,8 @@ For a good time, see `` SuperSig `` .SubSigA.subSig or `` SuperSig `` .SubSigB -######   module Buffer : sig ... - ######   end +###### module Buffer : sig ... +###### end `` Buffer `` .t @@ -357,7 +357,7 @@ After exception title. -######   exception Kaboom of unit +###### exception Kaboom of unit Unary exception constructor @@ -365,7 +365,7 @@ Unary exception constructor -######   exception Kablam of unit * unit +###### exception Kablam of unit * unit Binary exception constructor @@ -373,7 +373,7 @@ Binary exception constructor -######   exception Kapow of unit * unit +###### exception Kapow of unit * unit Unary exception constructor over binary tuple @@ -381,7 +381,7 @@ Unary exception constructor over binary tuple -######   exception EmptySig +###### exception EmptySig `` EmptySig `` is a module and `` EmptySig `` is this exception. @@ -389,7 +389,7 @@ Unary exception constructor over binary tuple -######   exception EmptySigAlias +###### exception EmptySigAlias `` EmptySigAlias `` is this exception. @@ -402,7 +402,7 @@ Unary exception constructor over binary tuple -######   type ('a, 'b) a_function = 'a -> 'b +###### type ('a, 'b) a_function = 'a -> 'b `` a_function `` is this type and `` a_function `` is the value below. @@ -410,7 +410,7 @@ Unary exception constructor over binary tuple -######   val a_function : x:int -> int +###### val a_function : x:int -> int This is `` a_function `` with param and return type. @@ -430,17 +430,17 @@ This is `` a_function `` with param and return type. -######   val fun_fun_fun : ((int, int) a_function, (unit, unit) a_function) a_function +###### val fun_fun_fun : ((int, int) a_function, (unit, unit) a_function) a_function -######   val fun_maybe : ?yes:unit -> unit -> int +###### val fun_maybe : ?yes:unit -> unit -> int -######   val not_found : unit -> unit +###### val not_found : unit -> unit @raises Not_found : That's all it does @@ -451,7 +451,7 @@ This is `` a_function `` with param and return type. -######   val ocaml_org : string +###### val ocaml_org : string @see http://ocaml.org/ : The OCaml Web site @@ -462,7 +462,7 @@ This is `` a_function `` with param and return type. -######   val some_file : string +###### val some_file : string @see `` some_file `` : The file called `` some_file `` @@ -473,7 +473,7 @@ This is `` a_function `` with param and return type. -######   val some_doc : string +###### val some_doc : string @see some_doc : The document called `` some_doc `` @@ -484,7 +484,7 @@ This is `` a_function `` with param and return type. -######   val since_mesozoic : unit +###### val since_mesozoic : unit This value was introduced in the Mesozoic era. @@ -496,7 +496,7 @@ This value was introduced in the Mesozoic era. -######   val changing : unit +###### val changing : unit This value has had changes in 1.0.0, 1.1.0, and 1.2.0. @@ -525,72 +525,72 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. -######   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 (*) : 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 +###### val (land) : unit @@ -600,8 +600,8 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. -######   module CollectionModule : sig ... - ######   end +###### module CollectionModule : sig ... +###### end This comment is for `` CollectionModule `` . @@ -609,7 +609,7 @@ This comment is for `` CollectionModule `` . -######   module type COLLECTION = sig +###### module type COLLECTION = sig This comment is for `` CollectionModule `` . @@ -632,7 +632,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -640,17 +640,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -658,24 +658,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -690,7 +690,7 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end module type of @@ -698,12 +698,12 @@ module type of -######   module Recollection (C : COLLECTION) : COLLECTION with type collection = C.element list and type element = C.collection +###### module Recollection (C : COLLECTION) : COLLECTION with type collection = C.element list and type element = C.collection -######   module type MMM = sig +###### module type MMM = sig ######         module C : sig @@ -713,7 +713,7 @@ This comment is for `` CollectionModule `` . -######                                 type collection +######                 type collection This comment is for `` collection `` . @@ -721,15 +721,15 @@ This comment is for `` collection `` . -######                                 type element +######                 type element -######                                 module InnerModuleA : sig +######                 module InnerModuleA : sig -######                                                                                                                                 type t = collection +######                         type t = collection This comment is for `` t `` . @@ -737,17 +737,17 @@ This comment is for `` t `` . -######                                                                                                                                 module InnerModuleA' : sig +######                         module InnerModuleA' : sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = (unit, unit) a_function +######                                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleA' `` . @@ -755,24 +755,24 @@ This comment is for `` InnerModuleA' `` . -######                                                                                                                                 module type InnerModuleTypeA' = sig +######                         module type InnerModuleTypeA' = sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = InnerModuleA'.t +######                                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleTypeA' `` . - ######   end +######                 end This comment is for `` InnerModuleA `` . @@ -780,35 +780,35 @@ This comment is for `` InnerModuleA `` . -######                                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +######                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . - ######   end +######         end - ######   end +###### end -######   module type RECOLLECTION = sig +###### module type RECOLLECTION = sig ######         module C = Recollection(CollectionModule) - ######   end +###### end -######   module type RecollectionModule = sig +###### module type RecollectionModule = sig ######         type collection = CollectionModule.element list @@ -824,7 +824,7 @@ This comment is for `` InnerModuleTypeA `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -832,17 +832,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -850,24 +850,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -882,12 +882,12 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end -######   module type A = sig +###### module type A = sig ######         type t @@ -902,7 +902,7 @@ This comment is for `` CollectionModule `` . -######                                 type collection +######                 type collection This comment is for `` collection `` . @@ -910,15 +910,15 @@ This comment is for `` collection `` . -######                                 type element +######                 type element -######                                 module InnerModuleA : sig +######                 module InnerModuleA : sig -######                                                                                                                                 type t = collection +######                         type t = collection This comment is for `` t `` . @@ -926,17 +926,17 @@ This comment is for `` t `` . -######                                                                                                                                 module InnerModuleA' : sig +######                         module InnerModuleA' : sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = (unit, unit) a_function +######                                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleA' `` . @@ -944,24 +944,24 @@ This comment is for `` InnerModuleA' `` . -######                                                                                                                                 module type InnerModuleTypeA' = sig +######                         module type InnerModuleTypeA' = sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = InnerModuleA'.t +######                                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleTypeA' `` . - ######   end +######                 end This comment is for `` InnerModuleA `` . @@ -969,23 +969,23 @@ This comment is for `` InnerModuleA `` . -######                                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +######                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . - ######   end +######         end - ######   end +###### end -######   module type B = sig +###### module type B = sig ######         type t @@ -1000,7 +1000,7 @@ This comment is for `` CollectionModule `` . -######                                 type collection +######                 type collection This comment is for `` collection `` . @@ -1008,15 +1008,15 @@ This comment is for `` collection `` . -######                                 type element +######                 type element -######                                 module InnerModuleA : sig +######                 module InnerModuleA : sig -######                                                                                                                                 type t = collection +######                         type t = collection This comment is for `` t `` . @@ -1024,17 +1024,17 @@ This comment is for `` t `` . -######                                                                                                                                 module InnerModuleA' : sig +######                         module InnerModuleA' : sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = (unit, unit) a_function +######                                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleA' `` . @@ -1042,24 +1042,24 @@ This comment is for `` InnerModuleA' `` . -######                                                                                                                                 module type InnerModuleTypeA' = sig +######                         module type InnerModuleTypeA' = sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = InnerModuleA'.t +######                                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleTypeA' `` . - ######   end +######                 end This comment is for `` InnerModuleA `` . @@ -1067,23 +1067,23 @@ This comment is for `` InnerModuleA `` . -######                                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +######                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . - ######   end +######         end - ######   end +###### end -######   module type C = sig +###### module type C = sig ######         type t @@ -1098,7 +1098,7 @@ This comment is for `` CollectionModule `` . -######                                 type collection +######                 type collection This comment is for `` collection `` . @@ -1106,15 +1106,15 @@ This comment is for `` collection `` . -######                                 type element +######                 type element -######                                 module InnerModuleA : sig +######                 module InnerModuleA : sig -######                                                                                                                                 type t = collection +######                         type t = collection This comment is for `` t `` . @@ -1122,17 +1122,17 @@ This comment is for `` t `` . -######                                                                                                                                 module InnerModuleA' : sig +######                         module InnerModuleA' : sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = (unit, unit) a_function +######                                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleA' `` . @@ -1140,24 +1140,24 @@ This comment is for `` InnerModuleA' `` . -######                                                                                                                                 module type InnerModuleTypeA' = sig +######                         module type InnerModuleTypeA' = sig -######                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                                 type t = InnerModuleA'.t +######                                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                         end This comment is for `` InnerModuleTypeA' `` . - ######   end +######                 end This comment is for `` InnerModuleA `` . @@ -1165,20 +1165,20 @@ This comment is for `` InnerModuleA `` . -######                                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +######                 module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . - ######   end +######         end - ######   end +###### end This module type includes two signatures. @@ -1186,8 +1186,8 @@ This module type includes two signatures. -######   module FunctorTypeOf (Collection : module type of CollectionModule) : sig ... - ######   end +###### module FunctorTypeOf (Collection : module type of CollectionModule) : sig ... +###### end This comment is for `` FunctorTypeOf `` . @@ -1195,11 +1195,11 @@ This comment is for `` FunctorTypeOf `` . -######   module type IncludeModuleType = sig +###### module type IncludeModuleType = sig - ######   end +###### end This comment is for `` IncludeModuleType `` . @@ -1207,17 +1207,17 @@ This comment is for `` IncludeModuleType `` . -######   module type ToInclude = sig +###### module type ToInclude = sig ######         module IncludedA : sig -######                                 type t +######                 type t - ######   end +######         end @@ -1225,33 +1225,33 @@ This comment is for `` IncludeModuleType `` . ######         module type IncludedB = sig -######                                 type s +######                 type s - ######   end +######         end - ######   end +###### end -######   module IncludedA : sig ... - ######   end +###### module IncludedA : sig ... +###### end -######   module type IncludedB = sig +###### module type IncludedB = sig ######         type s - ######   end +###### end @@ -1261,7 +1261,7 @@ This comment is for `` IncludeModuleType `` . -######   type record = { +###### type record = { ######         `` field1 : int; `` @@ -1290,7 +1290,7 @@ This comment is also for `` record `` . -######   type mutable_record = { +###### type mutable_record = { ######         `` mutable a : int; `` @@ -1322,7 +1322,7 @@ This comment is also for `` record `` . -######   type universe_record = { +###### type universe_record = { ######         `` nihilate : a. 'a -> unit; `` @@ -1334,7 +1334,7 @@ This comment is also for `` record `` . -######   type variant = +###### type variant = ######         | TagA @@ -1381,7 +1381,7 @@ This comment is also for `` variant `` . -######   type poly_variant = [ +###### type poly_variant = [ ######         `` | `` `` `TagA `` @@ -1406,7 +1406,7 @@ Wow! It was a polymorphic variant! -######   type (_, _) full_gadt = +###### type (_, _) full_gadt = ######         | Tag : (unit, unit) full_gadt @@ -1445,7 +1445,7 @@ Wow! It was a GADT! -######   type 'a partial_gadt = +###### type 'a partial_gadt = ######         | AscribeTag : 'a partial_gadt @@ -1477,7 +1477,7 @@ Wow! It was a mixed GADT! -######   type alias = variant +###### type alias = variant This comment is for `` alias `` . @@ -1485,7 +1485,7 @@ This comment is for `` alias `` . -######   type tuple = (alias * alias) * alias * (alias * alias) +###### type tuple = (alias * alias) * alias * (alias * alias) This comment is for `` tuple `` . @@ -1493,7 +1493,7 @@ This comment is for `` tuple `` . -######   type variant_alias = variant = +###### type variant_alias = variant = ######         | TagA @@ -1529,7 +1529,7 @@ This comment is for `` variant_alias `` . -######   type record_alias = record = { +###### type record_alias = record = { ######         `` field1 : int; `` @@ -1551,7 +1551,7 @@ This comment is for `` record_alias `` . -######   type poly_variant_union = [ +###### type poly_variant_union = [ ######         `` | `` `` poly_variant `` @@ -1573,7 +1573,7 @@ This comment is for `` poly_variant_union `` . -######   type 'a poly_poly_variant = [ +###### type 'a poly_poly_variant = [ ######         `` | `` `` `TagA of 'a `` @@ -1585,7 +1585,7 @@ This comment is for `` poly_variant_union `` . -######   type ('a, 'b) bin_poly_poly_variant = [ +###### type ('a, 'b) bin_poly_poly_variant = [ ######         `` | `` `` `TagA of 'a `` @@ -1604,42 +1604,42 @@ This comment is for `` poly_variant_union `` . -######   type 'a open_poly_variant = [> `TagA ] as 'a +###### type 'a open_poly_variant = [> `TagA ] as 'a -######   type 'a open_poly_variant2 = [> `ConstrB of int ] as 'a +###### type 'a open_poly_variant2 = [> `ConstrB of int ] as 'a -######   type 'a open_poly_variant_alias = 'a open_poly_variant open_poly_variant2 +###### type 'a open_poly_variant_alias = 'a open_poly_variant open_poly_variant2 -######   type 'a poly_fun = [> `ConstrB of int ] as 'a -> 'a +###### type 'a poly_fun = [> `ConstrB of int ] as 'a -> 'a -######   type 'a poly_fun_constraint = 'a -> 'a constraint 'a = [> `TagA ] +###### type 'a poly_fun_constraint = 'a -> 'a constraint 'a = [> `TagA ] -######   type 'a closed_poly_variant = [< `One | `Two ] as 'a +###### type 'a closed_poly_variant = [< `One | `Two ] as 'a -######   type 'a clopen_poly_variant = [< `One | `Two of int | `Three Two Three ] as 'a +###### type 'a clopen_poly_variant = [< `One | `Two of int | `Three Two Three ] as 'a -######   type nested_poly_variant = [ +###### type nested_poly_variant = [ ######         `` | `` `` `A `` @@ -1672,7 +1672,7 @@ This comment is for `` poly_variant_union `` . -######   type ('a, 'b) full_gadt_alias = ('a, 'b) full_gadt = +###### type ('a, 'b) full_gadt_alias = ('a, 'b) full_gadt = ######         | Tag : (unit, unit) full_gadt_alias @@ -1708,7 +1708,7 @@ This comment is for `` full_gadt_alias `` . -######   type 'a partial_gadt_alias = 'a partial_gadt = +###### type 'a partial_gadt_alias = 'a partial_gadt = ######         | AscribeTag : 'a partial_gadt_alias @@ -1737,7 +1737,7 @@ This comment is for `` partial_gadt_alias `` . -######   exception Exn_arrow : unit -> exn +###### exception Exn_arrow : unit -> exn This comment is for `` Exn_arrow `` . @@ -1745,7 +1745,7 @@ This comment is for `` Exn_arrow `` . -######   type mutual_constr_a = +###### type mutual_constr_a = ######         | A @@ -1769,7 +1769,7 @@ This comment is for `` mutual_constr_a `` then `` mutual_constr_b `` . -######   and mutual_constr_b = +###### and mutual_constr_b = ######         | B @@ -1793,37 +1793,37 @@ This comment is for `` mutual_constr_b `` then `` mutual_constr_a `` . -######   type rec_obj = < f : int; g : unit -> unit; h : rec_obj; > +###### type rec_obj = < f : int; g : unit -> unit; h : rec_obj; > -######   type 'a open_obj = < f : int; g : unit -> unit; .. > as 'a +###### type 'a open_obj = < f : int; g : unit -> unit; .. > as 'a -######   type 'a oof = < a : unit; .. > as 'a -> 'a +###### type 'a oof = < a : unit; .. > as 'a -> 'a -######   type 'a any_obj = < .. > as 'a +###### type 'a any_obj = < .. > as 'a -######   type empty_obj = < > +###### type empty_obj = < > -######   type one_meth = < meth : unit; > +###### type one_meth = < meth : unit; > -######   type ext = .. +###### type ext = .. A mystery wrapped in an ellipsis @@ -1831,7 +1831,7 @@ A mystery wrapped in an ellipsis -######   type ext += +###### type ext += ######         | ExtA @@ -1843,7 +1843,7 @@ A mystery wrapped in an ellipsis -######   type ext += +###### type ext += ######         | ExtB @@ -1855,7 +1855,7 @@ A mystery wrapped in an ellipsis -######   type ext += +###### type ext += ######         | ExtC of unit @@ -1874,7 +1874,7 @@ A mystery wrapped in an ellipsis -######   type ext += +###### type ext += ######         | ExtE @@ -1886,7 +1886,7 @@ A mystery wrapped in an ellipsis -######   type ext += +###### type ext += ######         | ExtF @@ -1898,7 +1898,7 @@ A mystery wrapped in an ellipsis -######   type 'a poly_ext = .. +###### type 'a poly_ext = .. 'a poly_ext @@ -1906,7 +1906,7 @@ A mystery wrapped in an ellipsis -######   type poly_ext += +###### type poly_ext += ######         | Foo of 'b @@ -1927,7 +1927,7 @@ A mystery wrapped in an ellipsis -######   type poly_ext += +###### type poly_ext += ######         | Quux of 'c @@ -1941,13 +1941,13 @@ A mystery wrapped in an ellipsis -######   module ExtMod : sig ... - ######   end +###### module ExtMod : sig ... +###### end -######   type ExtMod.t += +###### type ExtMod.t += ######         | ZzzTop0 @@ -1961,7 +1961,7 @@ A mystery wrapped in an ellipsis -######   type ExtMod.t += +###### type ExtMod.t += ######         | ZzzTop of unit @@ -1975,7 +1975,7 @@ A mystery wrapped in an ellipsis -######   val launch_missiles : unit -> unit +###### val launch_missiles : unit -> unit Rotate keys on my mark... @@ -1983,7 +1983,7 @@ Rotate keys on my mark... -######   type my_mod = (module COLLECTION) +###### type my_mod = (module COLLECTION) A brown paper package tied up with string @@ -1991,164 +1991,164 @@ A brown paper package tied up with string -######   class empty_class : object ... - ######   end +###### class empty_class : object ... +###### end -######   class one_method_class : object ... - ######   end +###### class one_method_class : object ... +###### end -######   class two_method_class : object ... - ######   end +###### class two_method_class : object ... +###### end -######   class 'a param_class : 'a -> object ... - ######   end +###### class 'a param_class : 'a -> object ... +###### end -######   type my_unit_object = unit param_class +###### type my_unit_object = unit param_class -######   type 'a my_unit_class = unit param_class as 'a +###### type 'a my_unit_class = unit param_class as 'a -######   module Dep1 : sig ... - ######   end +###### module Dep1 : sig ... +###### end -######   module Dep2 (Arg : sig ... - ######   end) : sig ... - ######   end +###### module Dep2 (Arg : sig ... +###### end) : sig ... +###### end -######   type dep1 = Dep2(Dep1).B.c +###### type dep1 = Dep2(Dep1).B.c -######   module Dep3 : sig ... - ######   end +###### module Dep3 : sig ... +###### end -######   module Dep4 : sig ... - ######   end +###### module Dep4 : sig ... +###### end -######   module Dep5 (Arg : sig ... - ######   end) : sig ... - ######   end +###### module Dep5 (Arg : sig ... +###### end) : sig ... +###### end -######   type dep2 = Dep5(Dep4).Z.X.b +###### type dep2 = Dep5(Dep4).Z.X.b -######   type dep3 = Dep5(Dep4).Z.Y.a +###### type dep3 = Dep5(Dep4).Z.Y.a -######   module Dep6 : sig ... - ######   end +###### module Dep6 : sig ... +###### end -######   module Dep7 (Arg : sig ... - ######   end) : sig ... - ######   end +###### module Dep7 (Arg : sig ... +###### end) : sig ... +###### end -######   type dep4 = Dep7(Dep6).M.Y.d +###### type dep4 = Dep7(Dep6).M.Y.d -######   module Dep8 : sig ... - ######   end +###### module Dep8 : sig ... +###### end -######   module Dep9 (X : sig ... - ######   end) : sig ... - ######   end +###### module Dep9 (X : sig ... +###### end) : sig ... +###### end -######   module type Dep10 = sig +###### module type Dep10 = sig ######         type t = int - ######   end +###### end -######   module Dep11 : sig ... - ######   end +###### module Dep11 : sig ... +###### end -######   module Dep12 (Arg : sig ... - ######   end) : sig ... - ######   end +###### module Dep12 (Arg : sig ... +###### end) : sig ... +###### end -######   module Dep13 : Dep12(Dep11).T +###### module Dep13 : Dep12(Dep11).T -######   type dep5 = Dep13.c +###### type dep5 = Dep13.c -######   module type With1 = sig +###### module type With1 = sig ######         module M : sig -######                                 module type S +######                 module type S - ######   end +######         end @@ -2157,107 +2157,107 @@ A brown paper package tied up with string - ######   end +###### end -######   module With2 : sig ... - ######   end +###### module With2 : sig ... +###### end -######   module With3 : With1 with module M = With2 +###### module With3 : With1 with module M = With2 -######   type with1 = With3.N.t +###### type with1 = With3.N.t -######   module With4 : With1 with module M := With2 +###### module With4 : With1 with module M := With2 -######   type with2 = With4.N.t +###### type with2 = With4.N.t -######   module With5 : sig ... - ######   end +###### module With5 : sig ... +###### end -######   module With6 : sig ... - ######   end +###### module With6 : sig ... +###### end -######   module With7 (X : sig ... - ######   end) : sig ... - ######   end +###### module With7 (X : sig ... +###### end) : sig ... +###### end -######   module type With8 = sig +###### module type With8 = sig ######         module M : sig -######                                 module type S = sig +######                 module type S = sig -######                                                                                                                                 type t +######                         type t - ######   end +######                 end -######                                 module N : sig +######                 module N : sig -######                                                                                                                                 type t = With5.N.t +######                         type t = With5.N.t - ######   end +######                 end - ######   end +######         end - ######   end +###### end -######   module With9 : sig ... - ######   end +###### module With9 : sig ... +###### end -######   module With10 : sig ... - ######   end +###### module With10 : sig ... +###### end -######   module type With11 = sig +###### module type With11 = sig ######         module M = With9 @@ -2268,96 +2268,96 @@ A brown paper package tied up with string ######         module N : sig -######                                 type t = int +######                 type t = int - ######   end +######         end - ######   end +###### end -######   module type NestedInclude1 = sig +###### module type NestedInclude1 = sig ######         module type NestedInclude2 = sig -######                                 type nested_include +######                 type nested_include - ######   end +######         end - ######   end +###### end -######   module type NestedInclude2 = sig +###### module type NestedInclude2 = sig ######         type nested_include - ######   end +###### end -######   type nested_include = int +###### type nested_include = int -######   module DoubleInclude1 : sig ... - ######   end +###### module DoubleInclude1 : sig ... +###### end -######   module DoubleInclude3 : sig ... - ######   end +###### module DoubleInclude3 : sig ... +###### end -######   type double_include +###### type double_include -######   module IncludeInclude1 : sig ... - ######   end +###### module IncludeInclude1 : sig ... +###### end -######   module type IncludeInclude2 = sig +###### module type IncludeInclude2 = sig ######         type include_include - ######   end +###### end -######   type include_include +###### type include_include -# Trying the {!modules: ...} command. +#:indexmodules Trying the {!modules: ...} command. With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references. @@ -2402,17 +2402,17 @@ With odoc, everything should be resolved (and linked) but only toplevel units wi -# Playing with @canonical paths +#:playing-with-@canonical-paths Playing with @canonical paths -######   module CanonicalTest : sig ... - ######   end +###### module CanonicalTest : sig ... +###### end -######   val test : 'a CanonicalTest.Base__.List.t -> unit +###### val test : 'a CanonicalTest.Base__.List.t -> unit Some ref to `` CanonicalTest `` .Base__Tests.C.t and `` CanonicalTest `` .Base__Tests.L.id. But also to `` CanonicalTest `` .Base__.List and `` CanonicalTest `` .Base__.List.t @@ -2420,12 +2420,12 @@ Some ref to `` CanonicalTest `` .Base__Tests.C.t and `` CanonicalTest `` .Base -# Aliases again +#:aliases Aliases again -######   module Aliases : sig ... - ######   end +###### module Aliases : sig ... +###### end Let's imitate jst's layout. @@ -2433,7 +2433,7 @@ Let's imitate jst's layout. -# Section title splicing +#:section-title-splicing Section title splicing I can refer to @@ -2463,24 +2463,24 @@ And just to make sure we do not mess up: -# New reference syntax +#:new-reference-syntax New reference syntax -######   module type M = sig +###### module type M = sig ######         type t - ######   end +###### end -######   module M : sig ... - ######   end +###### module M : sig ... +###### end @@ -2493,8 +2493,8 @@ Here goes: -######   module Only_a_module : sig ... - ######   end +###### module Only_a_module : sig ... +###### end @@ -2509,7 +2509,7 @@ Some here should fail: -######   module type TypeExt = sig +###### module type TypeExt = sig ######         type t = .. @@ -2520,7 +2520,7 @@ Some here should fail: ######         type t += -######                                 | C +######                 | C @@ -2533,17 +2533,17 @@ Some here should fail: - ######   end +###### end -######   type new_t = .. +###### type new_t = .. -######   type new_t += +###### type new_t += ######         | C @@ -2555,13 +2555,13 @@ Some here should fail: -######   module type TypeExtPruned = sig +###### module type TypeExtPruned = sig ######         type new_t += -######                                 | C +######                 | C @@ -2574,7 +2574,7 @@ Some here should fail: - ######   end +###### end OcamlaryEmpty @@ -2597,7 +2597,7 @@ OcamlaryEmpty An ambiguous, misnamed module type -######   type t +###### type t OcamlaryMissingComment @@ -2608,7 +2608,7 @@ OcamlaryMissingComment An ambiguous, misnamed module type -######   type t +###### type t OcamlaryEmptySig @@ -2646,7 +2646,7 @@ OcamlaryOne Module `` Ocamlary.One `` -######   type one +###### type one OcamlarySigForMod @@ -2657,25 +2657,25 @@ OcamlarySigForMod There's a signature in a module in this signature. -######   module Inner : sig +###### module Inner : sig ######         module type Empty = sig - ######   end +######         end - ######   end +###### end OcamlarySigForModInner Module `` SigForMod.Inner `` -######   module type Empty = sig +###### module type Empty = sig - ######   end +###### end OcamlarySigForModInnerEmpty @@ -2686,7 +2686,7 @@ OcamlarySuperSig Module type `` Ocamlary.SuperSig `` -######   module type SubSigA = sig +###### module type SubSigA = sig #### A Labeled Section Header Inside of a Signature @@ -2702,20 +2702,20 @@ OcamlarySuperSig ######         module SubSigAMod : sig -######                                 type sub_sig_a_mod +######                 type sub_sig_a_mod - ######   end +######         end - ######   end +###### end -######   module type SubSigB = sig +###### module type SubSigB = sig #### Another Labeled Section Header Inside of a Signature @@ -2727,38 +2727,38 @@ OcamlarySuperSig - ######   end +###### end -######   module type EmptySig = sig +###### module type EmptySig = sig ######         type not_actually_empty - ######   end +###### end -######   module type One = sig +###### module type One = sig ######         type two - ######   end +###### end -######   module type SuperSig = sig +###### module type SuperSig = sig - ######   end +###### end OcamlarySuperSigSubSigA @@ -2770,26 +2770,26 @@ OcamlarySuperSigSubSigA -######   type t +###### type t -######   module SubSigAMod : sig +###### module SubSigAMod : sig ######         type sub_sig_a_mod - ######   end +###### end OcamlarySuperSigSubSigASubSigAMod Module `` SubSigA.SubSigAMod `` -######   type sub_sig_a_mod +###### type sub_sig_a_mod OcamlarySuperSigSubSigB @@ -2801,21 +2801,21 @@ OcamlarySuperSigSubSigB -######   type t +###### type t OcamlarySuperSigEmptySig Module type `` SuperSig.EmptySig `` -######   type not_actually_empty +###### type not_actually_empty OcamlarySuperSigOne Module type `` SuperSig.One `` -######   type two +###### type two OcamlarySuperSigSuperSig @@ -2830,7 +2830,7 @@ OcamlaryBuffer `` Buffer `` .t -######   val f : Stdlib.Buffer.t -> unit +###### val f : Stdlib.Buffer.t -> unit OcamlaryCollectionModule @@ -2841,7 +2841,7 @@ OcamlaryCollectionModule This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -2849,13 +2849,13 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig ... - ######   end +###### module InnerModuleA : sig ... +###### end This comment is for `` InnerModuleA `` . @@ -2863,7 +2863,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -2877,7 +2877,7 @@ OcamlaryCollectionModuleInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -2885,8 +2885,8 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig ... - ######   end +###### module InnerModuleA' : sig ... +###### end This comment is for `` InnerModuleA' `` . @@ -2894,7 +2894,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -2904,7 +2904,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -2918,7 +2918,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -2932,7 +2932,7 @@ OcamlaryCollectionModuleInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -2950,7 +2950,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -2958,12 +2958,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -2977,14 +2977,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -2995,21 +2995,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -3017,7 +3017,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -3031,7 +3031,7 @@ OcamlaryCOLLECTIONInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -3039,7 +3039,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -3049,7 +3049,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -3057,7 +3057,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -3067,7 +3067,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -3081,7 +3081,7 @@ OcamlaryCOLLECTIONInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -3095,7 +3095,7 @@ OcamlaryCOLLECTIONInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -3105,11 +3105,11 @@ OcamlaryRecollection Module `` Ocamlary.Recollection `` -# Parameters +#:parameters Parameters -######   module C : sig +###### module C : sig This comment is for `` CollectionModule `` . @@ -3132,7 +3132,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -3140,17 +3140,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -3158,24 +3158,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -3190,12 +3190,12 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end -# Signature +#:signature Signature This comment is for `` CollectionModule `` . @@ -3203,7 +3203,7 @@ This comment is for `` CollectionModule `` . -######   type collection = C.element list +###### type collection = C.element list This comment is for `` collection `` . @@ -3211,13 +3211,13 @@ This comment is for `` collection `` . -######   type element = C.collection +###### type element = C.collection -######   module InnerModuleA : sig ... - ######   end +###### module InnerModuleA : sig ... +###### end This comment is for `` InnerModuleA `` . @@ -3225,7 +3225,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -3239,7 +3239,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -3247,12 +3247,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -3266,14 +3266,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -3284,21 +3284,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -3306,7 +3306,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -3320,7 +3320,7 @@ OcamlaryRecollection1-CInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -3328,7 +3328,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -3338,7 +3338,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -3346,7 +3346,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -3356,7 +3356,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -3370,7 +3370,7 @@ OcamlaryRecollection1-CInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -3384,7 +3384,7 @@ OcamlaryRecollection1-CInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -3398,7 +3398,7 @@ OcamlaryRecollectionInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -3406,8 +3406,8 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig ... - ######   end +###### module InnerModuleA' : sig ... +###### end This comment is for `` InnerModuleA' `` . @@ -3415,7 +3415,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -3425,7 +3425,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -3439,7 +3439,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -3453,7 +3453,7 @@ OcamlaryRecollectionInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -3463,7 +3463,7 @@ OcamlaryMMM Module type `` Ocamlary.MMM `` -######   module C : sig +###### module C : sig This comment is for `` CollectionModule `` . @@ -3486,7 +3486,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -3494,17 +3494,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -3512,24 +3512,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -3544,7 +3544,7 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end OcamlaryMMMC @@ -3555,7 +3555,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -3563,12 +3563,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -3582,14 +3582,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -3600,21 +3600,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -3622,7 +3622,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -3636,7 +3636,7 @@ OcamlaryMMMCInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -3644,7 +3644,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -3654,7 +3654,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -3662,7 +3662,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -3672,7 +3672,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -3686,7 +3686,7 @@ OcamlaryMMMCInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -3700,7 +3700,7 @@ OcamlaryMMMCInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -3710,24 +3710,24 @@ OcamlaryRECOLLECTION Module type `` Ocamlary.RECOLLECTION `` -######   module C = Recollection(CollectionModule) +###### module C = Recollection(CollectionModule) OcamlaryRecollectionModule Module type `` Ocamlary.RecollectionModule `` -######   type collection = CollectionModule.element list +###### type collection = CollectionModule.element list -######   type element = CollectionModule.collection +###### type element = CollectionModule.collection -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -3741,14 +3741,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -3759,21 +3759,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -3781,7 +3781,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -3795,7 +3795,7 @@ OcamlaryRecollectionModuleInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -3803,7 +3803,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -3813,7 +3813,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -3821,7 +3821,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -3831,7 +3831,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -3845,7 +3845,7 @@ OcamlaryRecollectionModuleInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -3859,7 +3859,7 @@ OcamlaryRecollectionModuleInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -3869,12 +3869,12 @@ OcamlaryA Module type `` Ocamlary.A `` -######   type t +###### type t -######   module Q : sig +###### module Q : sig This comment is for `` CollectionModule `` . @@ -3897,7 +3897,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -3905,17 +3905,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -3923,24 +3923,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -3955,7 +3955,7 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end OcamlaryAQ @@ -3966,7 +3966,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -3974,12 +3974,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -3993,14 +3993,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -4011,21 +4011,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -4033,7 +4033,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -4047,7 +4047,7 @@ OcamlaryAQInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -4055,7 +4055,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -4065,7 +4065,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -4073,7 +4073,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -4083,7 +4083,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -4097,7 +4097,7 @@ OcamlaryAQInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -4111,7 +4111,7 @@ OcamlaryAQInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -4121,12 +4121,12 @@ OcamlaryB Module type `` Ocamlary.B `` -######   type t +###### type t -######   module Q : sig +###### module Q : sig This comment is for `` CollectionModule `` . @@ -4149,7 +4149,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -4157,17 +4157,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -4175,24 +4175,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -4207,7 +4207,7 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end OcamlaryBQ @@ -4218,7 +4218,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -4226,12 +4226,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -4245,14 +4245,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -4263,21 +4263,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -4285,7 +4285,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -4299,7 +4299,7 @@ OcamlaryBQInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -4307,7 +4307,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -4317,7 +4317,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -4325,7 +4325,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -4335,7 +4335,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -4349,7 +4349,7 @@ OcamlaryBQInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -4363,7 +4363,7 @@ OcamlaryBQInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -4382,12 +4382,12 @@ This module type includes two signatures. - it includes `` B `` with some substitution -######   type t +###### type t -######   module Q : sig +###### module Q : sig This comment is for `` CollectionModule `` . @@ -4410,7 +4410,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -4418,17 +4418,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -4436,24 +4436,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -4468,7 +4468,7 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end @@ -4481,7 +4481,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -4489,12 +4489,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -4508,14 +4508,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -4526,21 +4526,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -4548,7 +4548,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -4562,7 +4562,7 @@ OcamlaryCQInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -4570,7 +4570,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -4580,7 +4580,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -4588,7 +4588,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -4598,7 +4598,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -4612,7 +4612,7 @@ OcamlaryCQInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -4626,7 +4626,7 @@ OcamlaryCQInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -4640,11 +4640,11 @@ OcamlaryFunctorTypeOf This comment is for `` FunctorTypeOf `` . -# Parameters +#:parameters Parameters -######   module Collection : sig +###### module Collection : sig This comment is for `` CollectionModule `` . @@ -4667,7 +4667,7 @@ This comment is for `` collection `` . ######         module InnerModuleA : sig -######                                 type t = collection +######                 type t = collection This comment is for `` t `` . @@ -4675,17 +4675,17 @@ This comment is for `` t `` . -######                                 module InnerModuleA' : sig +######                 module InnerModuleA' : sig -######                                                                                                                                 type t = (unit, unit) a_function +######                         type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleA' `` . @@ -4693,24 +4693,24 @@ This comment is for `` InnerModuleA' `` . -######                                 module type InnerModuleTypeA' = sig +######                 module type InnerModuleTypeA' = sig -######                                                                                                                                 type t = InnerModuleA'.t +######                         type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######                 end This comment is for `` InnerModuleTypeA' `` . - ######   end +######         end This comment is for `` InnerModuleA `` . @@ -4725,16 +4725,16 @@ This comment is for `` InnerModuleTypeA `` . - ######   end +###### end -# Signature +#:signature Signature -######   type t = Collection.collection +###### type t = Collection.collection This comment is for `` t `` . @@ -4748,7 +4748,7 @@ This comment is for `` CollectionModule `` . -######   type collection +###### type collection This comment is for `` collection `` . @@ -4756,12 +4756,12 @@ This comment is for `` collection `` . -######   type element +###### type element -######   module InnerModuleA : sig +###### module InnerModuleA : sig ######         type t = collection @@ -4775,14 +4775,14 @@ This comment is for `` t `` . ######         module InnerModuleA' : sig -######                                 type t = (unit, unit) a_function +######                 type t = (unit, unit) a_function This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleA' `` . @@ -4793,21 +4793,21 @@ This comment is for `` InnerModuleA' `` . ######         module type InnerModuleTypeA' = sig -######                                 type t = InnerModuleA'.t +######                 type t = InnerModuleA'.t This comment is for `` t `` . - ######   end +######         end This comment is for `` InnerModuleTypeA' `` . - ######   end +###### end This comment is for `` InnerModuleA `` . @@ -4815,7 +4815,7 @@ This comment is for `` InnerModuleA `` . -######   module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' +###### module type InnerModuleTypeA = InnerModuleA.InnerModuleTypeA' This comment is for `` InnerModuleTypeA `` . @@ -4829,7 +4829,7 @@ OcamlaryFunctorTypeOf1-CollectionInnerModuleA This comment is for `` InnerModuleA `` . -######   type t = collection +###### type t = collection This comment is for `` t `` . @@ -4837,7 +4837,7 @@ This comment is for `` t `` . -######   module InnerModuleA' : sig +###### module InnerModuleA' : sig ######         type t = (unit, unit) a_function @@ -4847,7 +4847,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleA' `` . @@ -4855,7 +4855,7 @@ This comment is for `` InnerModuleA' `` . -######   module type InnerModuleTypeA' = sig +###### module type InnerModuleTypeA' = sig ######         type t = InnerModuleA'.t @@ -4865,7 +4865,7 @@ This comment is for `` t `` . - ######   end +###### end This comment is for `` InnerModuleTypeA' `` . @@ -4879,7 +4879,7 @@ OcamlaryFunctorTypeOf1-CollectionInnerModuleAInnerModuleA' This comment is for `` InnerModuleA' `` . -######   type t = (unit, unit) a_function +###### type t = (unit, unit) a_function This comment is for `` t `` . @@ -4893,7 +4893,7 @@ OcamlaryFunctorTypeOf1-CollectionInnerModuleAInnerModuleTypeA' This comment is for `` InnerModuleTypeA' `` . -######   type t = InnerModuleA'.t +###### type t = InnerModuleA'.t This comment is for `` t `` . @@ -4911,66 +4911,66 @@ OcamlaryToInclude Module type `` Ocamlary.ToInclude `` -######   module IncludedA : sig +###### module IncludedA : sig ######         type t - ######   end +###### end -######   module type IncludedB = sig +###### module type IncludedB = sig ######         type s - ######   end +###### end OcamlaryToIncludeIncludedA Module `` ToInclude.IncludedA `` -######   type t +###### type t OcamlaryToIncludeIncludedB Module type `` ToInclude.IncludedB `` -######   type s +###### type s OcamlaryIncludedA Module `` Ocamlary.IncludedA `` -######   type t +###### type t OcamlaryIncludedB Module type `` Ocamlary.IncludedB `` -######   type s +###### type s OcamlaryExtMod Module `` Ocamlary.ExtMod `` -######   type t = .. +###### type t = .. -######   type t += +###### type t += ######         | Leisureforce @@ -4988,107 +4988,107 @@ Ocamlaryone_method_class Class `` Ocamlary.one_method_class `` -######   method go : unit +###### method go : unit Ocamlarytwo_method_class Class `` Ocamlary.two_method_class `` -######   method one : one_method_class +###### method one : one_method_class -######   method undo : unit +###### method undo : unit Ocamlaryparam_class Class `` Ocamlary.param_class `` -######   method v : 'a +###### method v : 'a OcamlaryDep1 Module `` Ocamlary.Dep1 `` -######   module type S = sig +###### module type S = sig ######         class c : object -######                                 method m : int +######                 method m : int - ######   end +######         end - ######   end +###### end -######   module X : sig ... - ######   end +###### module X : sig ... +###### end OcamlaryDep1S Module type `` Dep1.S `` -######   class c : object +###### class c : object ######         method m : int - ######   end +###### end OcamlaryDep1Sc Class `` S.c `` -######   method m : int +###### method m : int OcamlaryDep1X Module `` Dep1.X `` -######   module Y : S +###### module Y : S OcamlaryDep1XY Module `` X.Y `` -######   class c : object ... - ######   end +###### class c : object ... +###### end OcamlaryDep1XYc Class `` Y.c `` -######   method m : int +###### method m : int OcamlaryDep2 Module `` Ocamlary.Dep2 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type S @@ -5099,150 +5099,150 @@ OcamlaryDep2 ######         module X : sig -######                                 module Y : S +######                 module Y : S - ######   end +######         end - ######   end +###### end -# Signature +#:signature Signature -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B = A.Y +###### module B = A.Y OcamlaryDep21-Arg Parameter `` Dep2.1-Arg `` -######   module type S +###### module type S -######   module X : sig +###### module X : sig ######         module Y : S - ######   end +###### end OcamlaryDep21-ArgX Module `` 1-Arg.X `` -######   module Y : S +###### module Y : S OcamlaryDep2A Module `` Dep2.A `` -######   module Y : Arg.S +###### module Y : Arg.S OcamlaryDep3 Module `` Ocamlary.Dep3 `` -######   type a +###### type a OcamlaryDep4 Module `` Ocamlary.Dep4 `` -######   module type T = sig +###### module type T = sig ######         type b - ######   end +###### end -######   module type S = sig +###### module type S = sig ######         module X : sig -######                                 type b +######                 type b - ######   end +######         end ######         module Y : sig - ######   end +######         end - ######   end +###### end -######   module X : T +###### module X : T OcamlaryDep4T Module type `` Dep4.T `` -######   type b +###### type b OcamlaryDep4S Module type `` Dep4.S `` -######   module X : sig +###### module X : sig ######         type b - ######   end +###### end -######   module Y : sig +###### module Y : sig - ######   end +###### end OcamlaryDep4SX Module `` S.X `` -######   type b +###### type b OcamlaryDep4SY @@ -5253,18 +5253,18 @@ OcamlaryDep4X Module `` Dep4.X `` -######   type b +###### type b OcamlaryDep5 Module `` Ocamlary.Dep5 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type T @@ -5275,18 +5275,18 @@ OcamlaryDep5 ######         module type S = sig -######                                 module X : T +######                 module X : T -######                                 module Y : sig +######                 module Y : sig - ######   end +######                 end - ######   end +######         end @@ -5295,28 +5295,28 @@ OcamlaryDep5 - ######   end +###### end -# Signature +#:signature Signature -######   module Z : Arg.S with module Y = Dep3 +###### module Z : Arg.S with module Y = Dep3 OcamlaryDep51-Arg Parameter `` Dep5.1-Arg `` -######   module type T +###### module type T -######   module type S = sig +###### module type S = sig ######         module X : T @@ -5326,30 +5326,30 @@ OcamlaryDep51-Arg ######         module Y : sig - ######   end +######         end - ######   end +###### end -######   module X : T +###### module X : T OcamlaryDep51-ArgS Module type `` 1-Arg.S `` -######   module X : T +###### module X : T -######   module Y : sig +###### module Y : sig - ######   end +###### end OcamlaryDep51-ArgSY @@ -5360,31 +5360,31 @@ OcamlaryDep5Z Module `` Dep5.Z `` -######   module X : Arg.T +###### module X : Arg.T -######   module Y = Dep3 +###### module Y = Dep3 OcamlaryDep6 Module `` Ocamlary.Dep6 `` -######   module type S = sig +###### module type S = sig ######         type d - ######   end +###### end -######   module type T = sig +###### module type T = sig ######         module type R = S @@ -5395,83 +5395,83 @@ OcamlaryDep6 ######         module Y : sig -######                                 type d +######                 type d - ######   end +######         end - ######   end +###### end -######   module X : T +###### module X : T OcamlaryDep6S Module type `` Dep6.S `` -######   type d +###### type d OcamlaryDep6T Module type `` Dep6.T `` -######   module type R = S +###### module type R = S -######   module Y : sig +###### module Y : sig ######         type d - ######   end +###### end OcamlaryDep6TY Module `` T.Y `` -######   type d +###### type d OcamlaryDep6X Module `` Dep6.X `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep6XY Module `` X.Y `` -######   type d +###### type d OcamlaryDep7 Module `` Ocamlary.Dep7 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type S @@ -5482,16 +5482,16 @@ OcamlaryDep7 ######         module type T = sig -######                                 module type R = S +######                 module type R = S -######                                 module Y : R +######                 module Y : R - ######   end +######         end @@ -5499,41 +5499,41 @@ OcamlaryDep7 ######         module X : sig -######                                 module type R = S +######                 module type R = S -######                                 module Y : R +######                 module Y : R - ######   end +######         end - ######   end +###### end -# Signature +#:signature Signature -######   module M : Arg.T +###### module M : Arg.T OcamlaryDep71-Arg Parameter `` Dep7.1-Arg `` -######   module type S +###### module type S -######   module type T = sig +###### module type T = sig ######         module type R = S @@ -5545,12 +5545,12 @@ OcamlaryDep71-Arg - ######   end +###### end -######   module X : sig +###### module X : sig ######         module type R = S @@ -5562,342 +5562,342 @@ OcamlaryDep71-Arg - ######   end +###### end OcamlaryDep71-ArgT Module type `` 1-Arg.T `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep71-ArgX Module `` 1-Arg.X `` -######   module type R = S +###### module type R = S -######   module Y : R +###### module Y : R OcamlaryDep7M Module `` Dep7.M `` -######   module type R = Arg.S +###### module type R = Arg.S -######   module Y : R +###### module Y : R OcamlaryDep8 Module `` Ocamlary.Dep8 `` -######   module type T = sig +###### module type T = sig ######         type t - ######   end +###### end OcamlaryDep8T Module type `` Dep8.T `` -######   type t +###### type t OcamlaryDep9 Module `` Ocamlary.Dep9 `` -# Parameters +#:parameters Parameters -######   module X : sig +###### module X : sig ######         module type T - ######   end +###### end -# Signature +#:signature Signature -######   module type T = X.T +###### module type T = X.T OcamlaryDep91-X Parameter `` Dep9.1-X `` -######   module type T +###### module type T OcamlaryDep10 Module type `` Ocamlary.Dep10 `` -######   type t = int +###### type t = int OcamlaryDep11 Module `` Ocamlary.Dep11 `` -######   module type S = sig +###### module type S = sig ######         class c : object -######                                 method m : int +######                 method m : int - ######   end +######         end - ######   end +###### end OcamlaryDep11S Module type `` Dep11.S `` -######   class c : object +###### class c : object ######         method m : int - ######   end +###### end OcamlaryDep11Sc Class `` S.c `` -######   method m : int +###### method m : int OcamlaryDep12 Module `` Ocamlary.Dep12 `` -# Parameters +#:parameters Parameters -######   module Arg : sig +###### module Arg : sig ######         module type S - ######   end +###### end -# Signature +#:signature Signature -######   module type T = Arg.S +###### module type T = Arg.S OcamlaryDep121-Arg Parameter `` Dep12.1-Arg `` -######   module type S +###### module type S OcamlaryDep13 Module `` Ocamlary.Dep13 `` -######   class c : object ... - ######   end +###### class c : object ... +###### end OcamlaryDep13c Class `` Dep13.c `` -######   method m : int +###### method m : int OcamlaryWith1 Module type `` Ocamlary.With1 `` -######   module M : sig +###### module M : sig ######         module type S - ######   end +###### end -######   module N : M.S +###### module N : M.S OcamlaryWith1M Module `` With1.M `` -######   module type S +###### module type S OcamlaryWith2 Module `` Ocamlary.With2 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end OcamlaryWith2S Module type `` With2.S `` -######   type t +###### type t OcamlaryWith3 Module `` Ocamlary.With3 `` -######   module M = With2 +###### module M = With2 -######   module N : M.S +###### module N : M.S OcamlaryWith3N Module `` With3.N `` -######   type t +###### type t OcamlaryWith4 Module `` Ocamlary.With4 `` -######   module N : With2.S +###### module N : With2.S OcamlaryWith4N Module `` With4.N `` -######   type t +###### type t OcamlaryWith5 Module `` Ocamlary.With5 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end -######   module N : S +###### module N : S OcamlaryWith5S Module type `` With5.S `` -######   type t +###### type t OcamlaryWith5N Module `` With5.N `` -######   type t +###### type t OcamlaryWith6 Module `` Ocamlary.With6 `` -######   module type T = sig +###### module type T = sig ######         module M : sig -######                                 module type S +######                 module type S -######                                 module N : S +######                 module N : S - ######   end +######         end - ######   end +###### end OcamlaryWith6T Module type `` With6.T `` -######   module M : sig +###### module M : sig ######         module type S @@ -5909,70 +5909,70 @@ OcamlaryWith6T - ######   end +###### end OcamlaryWith6TM Module `` T.M `` -######   module type S +###### module type S -######   module N : S +###### module N : S OcamlaryWith7 Module `` Ocamlary.With7 `` -# Parameters +#:parameters Parameters -######   module X : sig +###### module X : sig ######         module type T - ######   end +###### end -# Signature +#:signature Signature -######   module type T = X.T +###### module type T = X.T OcamlaryWith71-X Parameter `` With7.1-X `` -######   module type T +###### module type T OcamlaryWith8 Module type `` Ocamlary.With8 `` -######   module M : sig +###### module M : sig ######         module type S = sig -######                                 type t +######                 type t - ######   end +######         end @@ -5980,93 +5980,93 @@ OcamlaryWith8 ######         module N : sig -######                                 type t = With5.N.t +######                 type t = With5.N.t - ######   end +######         end - ######   end +###### end OcamlaryWith8M Module `` With8.M `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end -######   module N : sig +###### module N : sig ######         type t = With5.N.t - ######   end +###### end OcamlaryWith8MS Module type `` M.S `` -######   type t +###### type t OcamlaryWith8MN Module `` M.N `` -######   type t = With5.N.t +###### type t = With5.N.t OcamlaryWith9 Module `` Ocamlary.With9 `` -######   module type S = sig +###### module type S = sig ######         type t - ######   end +###### end OcamlaryWith9S Module type `` With9.S `` -######   type t +###### type t OcamlaryWith10 Module `` Ocamlary.With10 `` -######   module type T = sig +###### module type T = sig ######         module M : sig -######                                 module type S +######                 module type S - ######   end +######         end @@ -6075,7 +6075,7 @@ OcamlaryWith10 - ######   end +###### end `` With10.T `` is a submodule type. @@ -6089,183 +6089,183 @@ OcamlaryWith10T `` With10.T `` is a submodule type. -######   module M : sig +###### module M : sig ######         module type S - ######   end +###### end -######   module N : M.S +###### module N : M.S OcamlaryWith10TM Module `` T.M `` -######   module type S +###### module type S OcamlaryWith11 Module type `` Ocamlary.With11 `` -######   module M = With9 +###### module M = With9 -######   module N : sig +###### module N : sig ######         type t = int - ######   end +###### end OcamlaryWith11N Module `` With11.N `` -######   type t = int +###### type t = int OcamlaryNestedInclude1 Module type `` Ocamlary.NestedInclude1 `` -######   module type NestedInclude2 = sig +###### module type NestedInclude2 = sig ######         type nested_include - ######   end +###### end OcamlaryNestedInclude1NestedInclude2 Module type `` NestedInclude1.NestedInclude2 `` -######   type nested_include +###### type nested_include OcamlaryNestedInclude2 Module type `` Ocamlary.NestedInclude2 `` -######   type nested_include +###### type nested_include OcamlaryDoubleInclude1 Module `` Ocamlary.DoubleInclude1 `` -######   module DoubleInclude2 : sig ... - ######   end +###### module DoubleInclude2 : sig ... +###### end OcamlaryDoubleInclude1DoubleInclude2 Module `` DoubleInclude1.DoubleInclude2 `` -######   type double_include +###### type double_include OcamlaryDoubleInclude3 Module `` Ocamlary.DoubleInclude3 `` -######   module DoubleInclude2 : sig ... - ######   end +###### module DoubleInclude2 : sig ... +###### end OcamlaryDoubleInclude3DoubleInclude2 Module `` DoubleInclude3.DoubleInclude2 `` -######   type double_include +###### type double_include OcamlaryIncludeInclude1 Module `` Ocamlary.IncludeInclude1 `` -######   module type IncludeInclude2 = sig +###### module type IncludeInclude2 = sig ######         type include_include - ######   end +###### end OcamlaryIncludeInclude1IncludeInclude2 Module type `` IncludeInclude1.IncludeInclude2 `` -######   type include_include +###### type include_include OcamlaryIncludeInclude2 Module type `` Ocamlary.IncludeInclude2 `` -######   type include_include +###### type include_include OcamlaryCanonicalTest Module `` Ocamlary.CanonicalTest `` -######   module Base : sig ... - ######   end +###### module Base : sig ... +###### end -######   module List_modif : module type of Base.List with type 'c t = 'c Base.List.t +###### module List_modif : module type of Base.List with type 'c t = 'c Base.List.t OcamlaryCanonicalTestBase Module `` CanonicalTest.Base `` -######   module List : sig ... - ######   end +###### module List : sig ... +###### end OcamlaryCanonicalTestBaseList Module `` Base.List `` -######   type 'a t +###### type 'a t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t OcamlaryCanonicalTestList_modif Module `` CanonicalTest.List_modif `` -######   type 'c t = 'c Base.List.t +###### type 'c t = 'c Base.List.t -######   val id : 'a t -> 'a t +###### val id : 'a t -> 'a t OcamlaryAliases @@ -6276,49 +6276,49 @@ OcamlaryAliases Let's imitate jst's layout. -######   module Foo : sig ... - ######   end +###### module Foo : sig ... +###### end -######   module A' = Foo.A +###### module A' = Foo.A -######   type tata = Foo.A.t +###### type tata = Foo.A.t -######   type tbtb = Foo.B.t +###### type tbtb = Foo.B.t -######   type tete +###### type tete -######   type tata' = A'.t +###### type tata' = A'.t -######   type tete2 = Foo.E.t +###### type tete2 = Foo.E.t -######   module Std : sig ... - ######   end +###### module Std : sig ... +###### end -######   type stde = Std.E.t +###### type stde = Std.E.t @@ -6332,33 +6332,33 @@ Just for giggle, let's see what happens when we include `` Foo `` . -######   module A = Foo.A +###### module A = Foo.A -######   module B = Foo.B +###### module B = Foo.B -######   module C = Foo.C +###### module C = Foo.C -######   module D = Foo.D +###### module D = Foo.D -######   module E : sig ... - ######   end +###### module E : sig ... +###### end -######   type testa = A.t +###### type testa = A.t @@ -6367,225 +6367,225 @@ And also, let's refer to `` A.t `` and `` Foo.B.id `` -######   module P1 : sig ... - ######   end +###### module P1 : sig ... +###### end -######   module P2 : sig ... - ######   end +###### module P2 : sig ... +###### end -######   module X1 = P2.Z +###### module X1 = P2.Z -######   module X2 = P2.Z +###### module X2 = P2.Z -######   type p1 = X1.t +###### type p1 = X1.t -######   type p2 = X2.t +###### type p2 = X2.t OcamlaryAliasesFoo Module `` Aliases.Foo `` -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B : sig ... - ######   end +###### module B : sig ... +###### end -######   module C : sig ... - ######   end +###### module C : sig ... +###### end -######   module D : sig ... - ######   end +###### module D : sig ... +###### end -######   module E : sig ... - ######   end +###### module E : sig ... +###### end OcamlaryAliasesFooA Module `` Foo.A `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooB Module `` Foo.B `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooC Module `` Foo.C `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooD Module `` Foo.D `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesFooE Module `` Foo.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesStd Module `` Aliases.Std `` -######   module A = Foo.A +###### module A = Foo.A -######   module B = Foo.B +###### module B = Foo.B -######   module C = Foo.C +###### module C = Foo.C -######   module D = Foo.D +###### module D = Foo.D -######   module E = Foo.E +###### module E = Foo.E OcamlaryAliasesE Module `` Aliases.E `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesP1 Module `` Aliases.P1 `` -######   module Y : sig ... - ######   end +###### module Y : sig ... +###### end OcamlaryAliasesP1Y Module `` P1.Y `` -######   type t +###### type t -######   val id : t -> t +###### val id : t -> t OcamlaryAliasesP2 Module `` Aliases.P2 `` -######   module Z = Z +###### module Z = Z OcamlaryM Module type `` Ocamlary.M `` -######   type t +###### type t OcamlaryM Module `` Ocamlary.M `` -######   type t +###### type t OcamlaryOnly_a_module Module `` Ocamlary.Only_a_module `` -######   type t +###### type t OcamlaryTypeExt Module type `` Ocamlary.TypeExt `` -######   type t = .. +###### type t = .. -######   type t += +###### type t += ######         | C @@ -6597,14 +6597,14 @@ OcamlaryTypeExt -######   val f : t -> unit +###### val f : t -> unit OcamlaryTypeExtPruned Module type `` Ocamlary.TypeExtPruned `` -######   type new_t += +###### type new_t += ######         | C @@ -6616,5 +6616,5 @@ OcamlaryTypeExtPruned -######   val f : new_t -> unit +###### val f : new_t -> unit diff --git a/test/generators/markdown/Ocamlary.one_method_class.md b/test/generators/markdown/Ocamlary.one_method_class.md index 9103a7ef8e..bf6eeb1bd7 100644 --- a/test/generators/markdown/Ocamlary.one_method_class.md +++ b/test/generators/markdown/Ocamlary.one_method_class.md @@ -2,5 +2,5 @@ Ocamlaryone_method_class Class `` Ocamlary.one_method_class `` -######   method go : unit +###### method go : unit diff --git a/test/generators/markdown/Ocamlary.param_class.md b/test/generators/markdown/Ocamlary.param_class.md index 9617a83954..f3b15d1402 100644 --- a/test/generators/markdown/Ocamlary.param_class.md +++ b/test/generators/markdown/Ocamlary.param_class.md @@ -2,5 +2,5 @@ Ocamlaryparam_class Class `` Ocamlary.param_class `` -######   method v : 'a +###### method v : 'a diff --git a/test/generators/markdown/Ocamlary.two_method_class.md b/test/generators/markdown/Ocamlary.two_method_class.md index e89a0014d5..5be6c826d3 100644 --- a/test/generators/markdown/Ocamlary.two_method_class.md +++ b/test/generators/markdown/Ocamlary.two_method_class.md @@ -2,10 +2,10 @@ Ocamlarytwo_method_class Class `` Ocamlary.two_method_class `` -######   method one : one_method_class +###### method one : one_method_class -######   method undo : unit +###### method undo : unit diff --git a/test/generators/markdown/Recent.X.md b/test/generators/markdown/Recent.X.md index 2ad0443386..f265792637 100644 --- a/test/generators/markdown/Recent.X.md +++ b/test/generators/markdown/Recent.X.md @@ -2,20 +2,20 @@ RecentX Module `` Recent.X `` -######   module L := Z.Y +###### module L := Z.Y -######   type t = int Z.Y.X.t +###### type t = int Z.Y.X.t -######   type u := int +###### type u := int -######   type v = u Z.Y.X.t +###### type v = u Z.Y.X.t diff --git a/test/generators/markdown/Recent.Z.Y.X.md b/test/generators/markdown/Recent.Z.Y.X.md index 653d51d5f2..5de0bfc757 100644 --- a/test/generators/markdown/Recent.Z.Y.X.md +++ b/test/generators/markdown/Recent.Z.Y.X.md @@ -2,5 +2,5 @@ RecentZYX Module `` Y.X `` -######   type 'a t +###### type 'a t diff --git a/test/generators/markdown/Recent.Z.Y.md b/test/generators/markdown/Recent.Z.Y.md index a7622f96d3..a7a2979610 100644 --- a/test/generators/markdown/Recent.Z.Y.md +++ b/test/generators/markdown/Recent.Z.Y.md @@ -2,13 +2,13 @@ RecentZY Module `` Z.Y `` -######   module X : sig ... - ######   end +###### module X : sig ... +###### end RecentZYX Module `` Y.X `` -######   type 'a t +###### type 'a t diff --git a/test/generators/markdown/Recent.Z.md b/test/generators/markdown/Recent.Z.md index 61cbba596d..0d6c765349 100644 --- a/test/generators/markdown/Recent.Z.md +++ b/test/generators/markdown/Recent.Z.md @@ -2,21 +2,21 @@ RecentZ Module `` Recent.Z `` -######   module Y : sig ... - ######   end +###### module Y : sig ... +###### end RecentZY Module `` Z.Y `` -######   module X : sig ... - ######   end +###### module X : sig ... +###### end RecentZYX Module `` Y.X `` -######   type 'a t +###### type 'a t diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 7c24823a5a..bc18a708a3 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -2,14 +2,14 @@ Recent Module `` Recent `` -######   module type S = sig +###### module type S = sig - ######   end +###### end -######   module type S1 = sig +###### module type S1 = sig ## Parameters @@ -19,7 +19,7 @@ Recent ######         module _ : sig - ######   end +######         end @@ -28,12 +28,12 @@ Recent --- - ######   end +###### end -######   type variant = +###### type variant = ######         | A @@ -84,7 +84,7 @@ Recent -######   type _ gadt = +###### type _ gadt = ######         | A : int gadt @@ -119,7 +119,7 @@ Recent -######   type polymorphic_variant = [ +###### type polymorphic_variant = [ ######         `` | `` `` `A `` @@ -156,17 +156,17 @@ Recent -######   type empty_variant = | +###### type empty_variant = | -######   type nonrec nonrec_ = int +###### type nonrec nonrec_ = int -######   type empty_conj = +###### type empty_conj = ######         | X : [< `X of & 'a & int * float ] -> empty_conj @@ -178,7 +178,7 @@ Recent -######   type conj = +###### type conj = ######         | X : [< `X of int & [< `B of int & float ] ] -> conj @@ -190,42 +190,42 @@ Recent -######   val empty_conj : [< `X of & 'a & int * float ] +###### val empty_conj : [< `X of & 'a & int * float ] -######   val conj : [< `X of int & [< `B of int & float ] ] +###### val conj : [< `X of int & [< `B of int & float ] ] -######   module Z : sig ... - ######   end +###### module Z : sig ... +###### end -######   module X : sig ... - ######   end +###### module X : sig ... +###### end -######   module type PolyS = sig +###### module type PolyS = sig ######         type t = [ -######                                 `` | `` `` `A `` +######                 `` | `` `` `A `` -######                                 `` | `` `` `B `` +######                 `` | `` `` `B `` @@ -233,7 +233,7 @@ Recent - ######   end +###### end RecentS @@ -244,18 +244,18 @@ RecentS1 Module type `` Recent.S1 `` -# Parameters +#:parameters Parameters -######   module _ : sig +###### module _ : sig - ######   end +###### end -# Signature +#:signature Signature RecentS11-_ @@ -265,52 +265,52 @@ RecentZ Module `` Recent.Z `` -######   module Y : sig ... - ######   end +###### module Y : sig ... +###### end RecentZY Module `` Z.Y `` -######   module X : sig ... - ######   end +###### module X : sig ... +###### end RecentZYX Module `` Y.X `` -######   type 'a t +###### type 'a t RecentX Module `` Recent.X `` -######   module L := Z.Y +###### module L := Z.Y -######   type t = int Z.Y.X.t +###### type t = int Z.Y.X.t -######   type u := int +###### type u := int -######   type v = u Z.Y.X.t +###### type v = u Z.Y.X.t RecentPolyS Module type `` Recent.PolyS `` -######   type t = [ +###### type t = [ ######         `` | `` `` `A `` diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md index 7c3c361431..86af0e9844 100644 --- a/test/generators/markdown/Recent_impl.B.md +++ b/test/generators/markdown/Recent_impl.B.md @@ -2,7 +2,7 @@ Recent_implB Module `` Recent_impl.B `` -######   type t = +###### type t = ######         | B diff --git a/test/generators/markdown/Recent_impl.Foo.A.md b/test/generators/markdown/Recent_impl.Foo.A.md index 30fb0852d2..465201023b 100644 --- a/test/generators/markdown/Recent_impl.Foo.A.md +++ b/test/generators/markdown/Recent_impl.Foo.A.md @@ -2,7 +2,7 @@ Recent_implFooA Module `` Foo.A `` -######   type t = +###### type t = ######         | A diff --git a/test/generators/markdown/Recent_impl.Foo.B.md b/test/generators/markdown/Recent_impl.Foo.B.md index e703f59fc5..e8b28c35d8 100644 --- a/test/generators/markdown/Recent_impl.Foo.B.md +++ b/test/generators/markdown/Recent_impl.Foo.B.md @@ -2,7 +2,7 @@ Recent_implFooB Module `` Foo.B `` -######   type t = +###### type t = ######         | B diff --git a/test/generators/markdown/Recent_impl.Foo.md b/test/generators/markdown/Recent_impl.Foo.md index f5bda26593..e933fbe505 100644 --- a/test/generators/markdown/Recent_impl.Foo.md +++ b/test/generators/markdown/Recent_impl.Foo.md @@ -2,21 +2,21 @@ Recent_implFoo Module `` Recent_impl.Foo `` -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B : sig ... - ######   end +###### module B : sig ... +###### end Recent_implFooA Module `` Foo.A `` -######   type t = +###### type t = ######         | A @@ -30,7 +30,7 @@ Recent_implFooB Module `` Foo.B `` -######   type t = +###### type t = ######         | B diff --git a/test/generators/markdown/Recent_impl.md b/test/generators/markdown/Recent_impl.md index 0d0db2b4b2..4ff9ac1942 100644 --- a/test/generators/markdown/Recent_impl.md +++ b/test/generators/markdown/Recent_impl.md @@ -2,24 +2,24 @@ Recent_impl Module `` Recent_impl `` -######   module Foo : sig ... - ######   end +###### module Foo : sig ... +###### end -######   module B : sig ... - ######   end +###### module B : sig ... +###### end -######   type u +###### type u -######   module type S = sig +###### module type S = sig ######         module F : sig @@ -30,9 +30,9 @@ Recent_impl -######                                 module _ : sig +######                 module _ : sig - ######   end +######                 end @@ -42,18 +42,18 @@ Recent_impl -######                                 type t +######                 type t - ######   end +######         end ######         module X : sig - ######   end +######         end @@ -62,33 +62,33 @@ Recent_impl - ######   end +###### end -######   module B' = Foo.B +###### module B' = Foo.B Recent_implFoo Module `` Recent_impl.Foo `` -######   module A : sig ... - ######   end +###### module A : sig ... +###### end -######   module B : sig ... - ######   end +###### module B : sig ... +###### end Recent_implFooA Module `` Foo.A `` -######   type t = +###### type t = ######         | A @@ -102,7 +102,7 @@ Recent_implFooB Module `` Foo.B `` -######   type t = +###### type t = ######         | B @@ -116,7 +116,7 @@ Recent_implB Module `` Recent_impl.B `` -######   type t = +###### type t = ######         | B @@ -130,7 +130,7 @@ Recent_implS Module type `` Recent_impl.S `` -######   module F : sig +###### module F : sig ## Parameters @@ -140,7 +140,7 @@ Recent_implS ######         module _ : sig - ######   end +######         end @@ -154,41 +154,41 @@ Recent_implS - ######   end +###### end -######   module X : sig +###### module X : sig - ######   end +###### end -######   val f : F(X).t +###### val f : F(X).t Recent_implSF Module `` S.F `` -# Parameters +#:parameters Parameters -######   module _ : sig +###### module _ : sig - ######   end +###### end -# Signature +#:signature Signature -######   type t +###### type t Recent_implSF1-_ diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index ff4549ed73..cd1b695cae 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -6,11 +6,11 @@ Section This is the module comment. Eventually, sections won't be allowed in it. -# Empty section +#:empty-section Empty section -# Text only +#:text-only Text only Foo bar. @@ -18,7 +18,7 @@ Foo bar. -# Aside only +#:aside-only Aside only Foo bar. @@ -26,20 +26,20 @@ Foo bar. -# Value only +#:value-only Value only -######   val foo : unit +###### val foo : unit -# Empty section +#:empty-section Empty section -# within a comment +#:within-a-comment within a comment @@ -48,7 +48,7 @@ Foo bar. -# _This_ `` section `` **title** has markup +#:this-section-title-has-markup _This_ `` section `` **title** has markup But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. diff --git a/test/generators/markdown/Stop.N.md b/test/generators/markdown/Stop.N.md index 3441ea1ee9..b21a76e1bb 100644 --- a/test/generators/markdown/Stop.N.md +++ b/test/generators/markdown/Stop.N.md @@ -2,5 +2,5 @@ StopN Module `` Stop.N `` -######   val quux : int +###### val quux : int diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md index 5401d69e28..488b7d6f50 100644 --- a/test/generators/markdown/Stop.md +++ b/test/generators/markdown/Stop.md @@ -6,7 +6,7 @@ Stop This test cases exercises stop comments. -######   val foo : int +###### val foo : int This is normal commented text. @@ -25,18 +25,18 @@ Now, we have a nested module, and it has a stop comment between its two items. W -######   module N : sig ... - ######   end +###### module N : sig ... +###### end -######   val lol : int +###### val lol : int StopN Module `` Stop.N `` -######   val quux : int +###### val quux : int diff --git a/test/generators/markdown/Stop_dead_link_doc.Foo.md b/test/generators/markdown/Stop_dead_link_doc.Foo.md index f9244f7d0a..0c48996492 100644 --- a/test/generators/markdown/Stop_dead_link_doc.Foo.md +++ b/test/generators/markdown/Stop_dead_link_doc.Foo.md @@ -2,5 +2,5 @@ Stop_dead_link_docFoo Module `` Stop_dead_link_doc.Foo `` -######   type t +###### type t diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index bbd4266806..ccc63ee210 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -2,13 +2,13 @@ Stop_dead_link_doc Module `` Stop_dead_link_doc `` -######   module Foo : sig ... - ######   end +###### module Foo : sig ... +###### end -######   type foo = +###### type foo = ######         | Bar of Foo.t @@ -20,7 +20,7 @@ Stop_dead_link_doc -######   type bar = +###### type bar = ######         | Bar of { @@ -39,7 +39,7 @@ Stop_dead_link_doc -######   type foo_ = +###### type foo_ = ######         | Bar_ of int * Foo.t * int @@ -51,7 +51,7 @@ Stop_dead_link_doc -######   type bar_ = +###### type bar_ = ######         | Bar__ of Foo.t option @@ -63,27 +63,27 @@ Stop_dead_link_doc -######   type another_foo +###### type another_foo -######   type another_bar +###### type another_bar -######   type another_foo_ +###### type another_foo_ -######   type another_bar_ +###### type another_bar_ Stop_dead_link_docFoo Module `` Stop_dead_link_doc.Foo `` -######   type t +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Alias.md b/test/generators/markdown/Toplevel_comments.Alias.md index 4351a73140..36567efdbf 100644 --- a/test/generators/markdown/Toplevel_comments.Alias.md +++ b/test/generators/markdown/Toplevel_comments.Alias.md @@ -10,5 +10,5 @@ Doc of `` Alias `` . Doc of `` T `` , part 2. -######   type t +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Include_inline'.md b/test/generators/markdown/Toplevel_comments.Include_inline'.md index 1788840209..c88df59187 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline'.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline'.md @@ -10,5 +10,5 @@ Doc of `` Include_inline `` , part 1. Doc of `` Include_inline `` , part 2. -######   type t +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Include_inline.md b/test/generators/markdown/Toplevel_comments.Include_inline.md index bf0deb2c91..b5b40078e8 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline.md @@ -6,5 +6,5 @@ Toplevel_commentsInclude_inline Doc of `` T `` , part 2. -######   type t +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md index 33f072bf66..1949f06484 100644 --- a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -10,5 +10,5 @@ Toplevel_commentsRef_in_synopsis This reference should resolve in the context of this module, even when used as a synopsis. -######   type t +###### type t diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index 78208cb814..a4d8d90185 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -6,14 +6,14 @@ Toplevel_comments A doc comment at the beginning of a module is considered to be that module's doc. -######   module type T = sig +###### module type T = sig ######         type t - ######   end +###### end Doc of `` T `` , part 1. @@ -21,8 +21,8 @@ Doc of `` T `` , part 1. -######   module Include_inline : sig ... - ######   end +###### module Include_inline : sig ... +###### end Doc of `` T `` , part 2. @@ -30,8 +30,8 @@ Doc of `` T `` , part 2. -######   module Include_inline' : sig ... - ######   end +###### module Include_inline' : sig ... +###### end Doc of `` Include_inline `` , part 1. @@ -39,14 +39,14 @@ Doc of `` Include_inline `` , part 1. -######   module type Include_inline_T = sig +###### module type Include_inline_T = sig ######         type t - ######   end +###### end Doc of `` T `` , part 2. @@ -54,14 +54,14 @@ Doc of `` T `` , part 2. -######   module type Include_inline_T' = sig +###### module type Include_inline_T' = sig ######         type t - ######   end +###### end Doc of `` Include_inline_T' `` , part 1. @@ -69,8 +69,8 @@ Doc of `` Include_inline_T' `` , part 1. -######   module M : sig ... - ######   end +###### module M : sig ... +###### end Doc of `` M `` @@ -78,8 +78,8 @@ Doc of `` M `` -######   module M' : sig ... - ######   end +###### module M' : sig ... +###### end Doc of `` M' `` from outside @@ -87,8 +87,8 @@ Doc of `` M' `` from outside -######   module M'' : sig ... - ######   end +###### module M'' : sig ... +###### end Doc of `` M'' `` , part 1. @@ -96,7 +96,7 @@ Doc of `` M'' `` , part 1. -######   module Alias : T +###### module Alias : T Doc of `` Alias `` . @@ -104,8 +104,8 @@ Doc of `` Alias `` . -######   class c1 : int -> object ... - ######   end +###### class c1 : int -> object ... +###### end Doc of `` c1 `` , part 1. @@ -113,9 +113,9 @@ Doc of `` c1 `` , part 1. -######   class type ct = object +###### class type ct = object - ######   end +###### end Doc of `` ct `` , part 1. @@ -123,7 +123,7 @@ Doc of `` ct `` , part 1. -######   class c2 : ct +###### class c2 : ct Doc of `` c2 `` . @@ -131,8 +131,8 @@ Doc of `` c2 `` . -######   module Ref_in_synopsis : sig ... - ######   end +###### module Ref_in_synopsis : sig ... +###### end `` t `` . @@ -150,7 +150,7 @@ Doc of `` T `` , part 1. Doc of `` T `` , part 2. -######   type t +###### type t Toplevel_commentsInclude_inline @@ -161,7 +161,7 @@ Toplevel_commentsInclude_inline Doc of `` T `` , part 2. -######   type t +###### type t Toplevel_commentsInclude_inline' @@ -176,7 +176,7 @@ Doc of `` Include_inline `` , part 1. Doc of `` Include_inline `` , part 2. -######   type t +###### type t Toplevel_commentsInclude_inline_T @@ -187,7 +187,7 @@ Toplevel_commentsInclude_inline_T Doc of `` T `` , part 2. -######   type t +###### type t Toplevel_commentsInclude_inline_T' @@ -202,7 +202,7 @@ Doc of `` Include_inline_T' `` , part 1. Doc of `` Include_inline_T' `` , part 2. -######   type t +###### type t Toplevel_commentsM @@ -245,7 +245,7 @@ Doc of `` Alias `` . Doc of `` T `` , part 2. -######   type t +###### type t Toplevel_commentsc1 @@ -296,5 +296,5 @@ Toplevel_commentsRef_in_synopsis This reference should resolve in the context of this module, even when used as a synopsis. -######   type t +###### type t diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 64fa69cc50..7df1574551 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -2,7 +2,7 @@ Type Module `` Type `` -######   type abstract +###### type abstract Some _documentation_. @@ -10,77 +10,77 @@ Some _documentation_. -######   type alias = int +###### type alias = int -######   type private_ = private int +###### type private_ = private int -######   type 'a constructor = 'a +###### type 'a constructor = 'a -######   type arrow = int -> int +###### type arrow = int -> int -######   type higher_order = (int -> int) -> int +###### type higher_order = (int -> int) -> int -######   type labeled = l:int -> int +###### type labeled = l:int -> int -######   type optional = ?l:int -> int +###### type optional = ?l:int -> int -######   type labeled_higher_order = (l:int -> int) -> (?l:int -> int) -> int +###### type labeled_higher_order = (l:int -> int) -> (?l:int -> int) -> int -######   type pair = int * int +###### type pair = int * int -######   type parens_dropped = int * int +###### type parens_dropped = int * int -######   type triple = int * int * int +###### type triple = int * int * int -######   type nested_pair = (int * int) * int +###### type nested_pair = (int * int) * int -######   type instance = int constructor +###### type instance = int constructor -######   type long = labeled_higher_order -> [ `Bar | `Baz of triple ] -> pair -> labeled -> higher_order -> (string -> int) -> (int, float, char, string, char, unit) CamlinternalFormatBasics.fmtty -> nested_pair -> arrow -> string -> nested_pair array +###### type long = labeled_higher_order -> [ `Bar | `Baz of triple ] -> pair -> labeled -> higher_order -> (string -> int) -> (int, float, char, string, char, unit) CamlinternalFormatBasics.fmtty -> nested_pair -> arrow -> string -> nested_pair array -######   type variant_e = { +###### type variant_e = { ######         `` a : int; `` @@ -92,7 +92,7 @@ Some _documentation_. -######   type variant = +###### type variant = ######         | A @@ -136,7 +136,7 @@ Some _documentation_. -######   type variant_c = { +###### type variant_c = { ######         `` a : int; `` @@ -148,7 +148,7 @@ Some _documentation_. -######   type _ gadt = +###### type _ gadt = ######         | A : int gadt @@ -174,7 +174,7 @@ Some _documentation_. -######   type degenerate_gadt = +###### type degenerate_gadt = ######         | A : degenerate_gadt @@ -186,7 +186,7 @@ Some _documentation_. -######   type private_variant = private +###### type private_variant = private ######         | A @@ -198,7 +198,7 @@ Some _documentation_. -######   type record = { +###### type record = { ######         `` a : int; `` @@ -242,7 +242,7 @@ Some _documentation_. -######   type polymorphic_variant = [ +###### type polymorphic_variant = [ ######         `` | `` `` `A `` @@ -275,7 +275,7 @@ Some _documentation_. -######   type polymorphic_variant_extension = [ +###### type polymorphic_variant_extension = [ ######         `` | `` `` polymorphic_variant `` @@ -294,7 +294,7 @@ Some _documentation_. -######   type nested_polymorphic_variant = [ +###### type nested_polymorphic_variant = [ ######         `` | `` `` `A of [ `B | `C ] `` @@ -306,12 +306,12 @@ Some _documentation_. -######   type private_extenion#row +###### type private_extenion#row -######   and private_extenion = private [> +###### and private_extenion = private [> ######         `` | `` `` polymorphic_variant `` @@ -323,12 +323,12 @@ Some _documentation_. -######   type object_ = < a : int; b : int; c : int; > +###### type object_ = < a : int; b : int; c : int; > -######   module type X = sig +###### module type X = sig ######         type t @@ -340,112 +340,112 @@ Some _documentation_. - ######   end +###### end -######   type module_ = (module X) +###### type module_ = (module X) -######   type module_substitution = (module X with type t = int and type u = unit) +###### type module_substitution = (module X with type t = int and type u = unit) -######   type +'a covariant +###### type +'a covariant -######   type -'a contravariant +###### type -'a contravariant -######   type _ bivariant = int +###### type _ bivariant = int -######   type ('a, 'b) binary +###### type ('a, 'b) binary -######   type using_binary = (int, int) binary +###### type using_binary = (int, int) binary -######   type 'custom name +###### type 'custom name -######   type 'a constrained = 'a constraint 'a = int +###### type 'a constrained = 'a constraint 'a = int -######   type 'a exact_variant = 'a constraint 'a = [ `A | `B of int ] +###### type 'a exact_variant = 'a constraint 'a = [ `A | `B of int ] -######   type 'a lower_variant = 'a constraint 'a = [> `A | `B of int ] +###### type 'a lower_variant = 'a constraint 'a = [> `A | `B of int ] -######   type 'a any_variant = 'a constraint 'a = [> ] +###### type 'a any_variant = 'a constraint 'a = [> ] -######   type 'a upper_variant = 'a constraint 'a = [< `A | `B of int ] +###### type 'a upper_variant = 'a constraint 'a = [< `A | `B of int ] -######   type 'a named_variant = 'a constraint 'a = [< polymorphic_variant ] +###### type 'a named_variant = 'a constraint 'a = [< polymorphic_variant ] -######   type 'a exact_object = 'a constraint 'a = < a : int; b : int; > +###### type 'a exact_object = 'a constraint 'a = < a : int; b : int; > -######   type 'a lower_object = 'a constraint 'a = < a : int; b : int; .. > +###### type 'a lower_object = 'a constraint 'a = < a : int; b : int; .. > -######   type 'a poly_object = 'a constraint 'a = < a : a. 'a; > +###### type 'a poly_object = 'a constraint 'a = < a : a. 'a; > -######   type ('a, 'b) double_constrained = 'a * 'b constraint 'a = int constraint 'b = unit +###### type ('a, 'b) double_constrained = 'a * 'b constraint 'a = int constraint 'b = unit -######   type as_ = int as 'a * 'a +###### type as_ = int as 'a * 'a -######   type extensible = .. +###### type extensible = .. -######   type extensible += +###### type extensible += ######         | Extension @@ -468,7 +468,7 @@ Some _documentation_. -######   type mutually = +###### type mutually = ######         | A of recursive @@ -480,7 +480,7 @@ Some _documentation_. -######   and recursive = +###### and recursive = ######         | B of mutually @@ -492,17 +492,17 @@ Some _documentation_. -######   exception Foo of int * int +###### exception Foo of int * int TypeX Module type `` Type.X `` -######   type t +###### type t -######   type u +###### type u diff --git a/test/generators/markdown/Val.md b/test/generators/markdown/Val.md index c74f63e8fc..b963451651 100644 --- a/test/generators/markdown/Val.md +++ b/test/generators/markdown/Val.md @@ -2,7 +2,7 @@ Val Module `` Val `` -######   val documented : unit +###### val documented : unit Foo. @@ -10,12 +10,12 @@ Foo. -######   val undocumented : unit +###### val undocumented : unit -######   val documented_above : unit +###### val documented_above : unit Bar. diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index 4b934a3105..de06cb71a0 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -10,7 +10,7 @@ This is an `` .mld `` file. It doesn't have an auto-generated title, like modu It will have a TOC generated from section headings. -# Section +#:section Section This is a section. @@ -21,7 +21,7 @@ Another paragraph in section. -# Another section +#:another-section Another section This is another section.