From 124ef632b000f3b5cb6bf3318532b6914cde242e Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 15:01:40 +0200 Subject: [PATCH 1/3] Consistent output file names in all backends The latex and man backends were prefixing names differently than the HTML backend. This can create naming conflicts. This removes code that was hard to maintain. --- src/document/url.ml | 4 + src/document/url.mli | 3 + src/html/link.ml | 4 +- src/latex/generator.ml | 12 +- src/manpage/link.ml | 4 +- test/generators/latex/Alerts.tex | 20 +- test/generators/latex/Alias.X.tex | 4 +- test/generators/latex/Alias.tex | 4 +- test/generators/latex/Bugs.tex | 8 +- .../latex/Bugs_post_406.let_open'.tex | 2 +- test/generators/latex/Bugs_post_406.tex | 6 +- test/generators/latex/Bugs_pre_410.tex | 6 +- .../generators/latex/Class.empty_virtual'.tex | 2 +- test/generators/latex/Class.mutually'.tex | 2 +- test/generators/latex/Class.polymorphic'.tex | 2 +- test/generators/latex/Class.recursive'.tex | 2 +- test/generators/latex/Class.tex | 20 +- test/generators/latex/Class_comments.c.tex | 6 +- test/generators/latex/Class_comments.tex | 6 +- test/generators/latex/Class_comments.x.tex | 2 +- test/generators/latex/External.tex | 4 +- test/generators/latex/Functor.F1.tex | 6 +- test/generators/latex/Functor.F2.tex | 6 +- test/generators/latex/Functor.F3.tex | 6 +- test/generators/latex/Functor.F4.tex | 6 +- test/generators/latex/Functor.F5.tex | 4 +- test/generators/latex/Functor.tex | 20 +- test/generators/latex/Functor2.X.tex | 12 +- test/generators/latex/Functor2.tex | 18 +- test/generators/latex/Functor_ml.Foo'.tex | 6 +- test/generators/latex/Functor_ml.tex | 8 +- test/generators/latex/Include.tex | 24 +- test/generators/latex/Include2.tex | 12 +- test/generators/latex/Include_sections.tex | 24 +- test/generators/latex/Interlude.tex | 12 +- test/generators/latex/Labels.c.tex | 2 +- test/generators/latex/Labels.tex | 64 +- test/generators/latex/Markup.tex | 20 +- test/generators/latex/Module.tex | 80 +- test/generators/latex/Module_type_alias.tex | 28 +- test/generators/latex/Module_type_of.T.N.tex | 4 +- test/generators/latex/Module_type_of.T.tex | 8 +- test/generators/latex/Module_type_of.tex | 14 +- test/generators/latex/Module_type_subst.tex | 44 +- test/generators/latex/Nested.F.tex | 14 +- test/generators/latex/Nested.inherits.tex | 4 +- test/generators/latex/Nested.tex | 20 +- test/generators/latex/Nested.z.tex | 10 +- test/generators/latex/Ocamlary.Dep12.tex | 6 +- test/generators/latex/Ocamlary.Dep13.c.tex | 4 +- test/generators/latex/Ocamlary.Dep13.tex | 4 +- test/generators/latex/Ocamlary.Dep2.tex | 10 +- test/generators/latex/Ocamlary.Dep5.Z.tex | 6 +- test/generators/latex/Ocamlary.Dep5.tex | 12 +- test/generators/latex/Ocamlary.Dep7.M.tex | 6 +- test/generators/latex/Ocamlary.Dep7.tex | 14 +- test/generators/latex/Ocamlary.Dep9.tex | 6 +- .../latex/Ocamlary.FunctorTypeOf.tex | 16 +- .../latex/Ocamlary.ModuleWithSignature.tex | 4 +- .../Ocamlary.ModuleWithSignatureAlias.tex | 2 +- .../latex/Ocamlary.Recollection.tex | 26 +- test/generators/latex/Ocamlary.With3.N.tex | 4 +- test/generators/latex/Ocamlary.With3.tex | 6 +- test/generators/latex/Ocamlary.With4.N.tex | 4 +- test/generators/latex/Ocamlary.With4.tex | 4 +- test/generators/latex/Ocamlary.With7.tex | 6 +- .../generators/latex/Ocamlary.empty_class.tex | 2 +- .../latex/Ocamlary.one_method_class.tex | 4 +- .../generators/latex/Ocamlary.param_class.tex | 4 +- test/generators/latex/Ocamlary.tex | 724 +++++++++--------- .../latex/Ocamlary.two_method_class.tex | 6 +- test/generators/latex/Recent.tex | 70 +- test/generators/latex/Recent_impl.B.tex | 6 +- test/generators/latex/Recent_impl.tex | 26 +- test/generators/latex/Section.tex | 4 +- test/generators/latex/Stop.tex | 14 +- test/generators/latex/Stop_dead_link_doc.tex | 40 +- test/generators/latex/Stop_first_comment.tex | 4 +- test/generators/latex/Tag_link.tex | 16 +- .../latex/Toplevel_comments.Alias.tex | 4 +- .../generators/latex/Toplevel_comments.c1.tex | 2 +- .../generators/latex/Toplevel_comments.c2.tex | 2 +- test/generators/latex/Toplevel_comments.tex | 34 +- test/generators/latex/Type.tex | 182 ++--- test/generators/latex/Val.tex | 8 +- test/generators/latex/mld.tex | 2 +- test/generators/link.dune.inc | 78 +- ...n'.3o => Bugs_post_406.class-let_open'.3o} | 0 ...tual'.3o => Class.class-empty_virtual'.3o} | 0 ....mutually'.3o => Class.class-mutually'.3o} | 0 ...orphic'.3o => Class.class-polymorphic'.3o} | 0 ...ecursive'.3o => Class.class-recursive'.3o} | 0 ...omments.c.3o => Class_comments.class-c.3o} | 0 ...omments.x.3o => Class_comments.class-x.3o} | 0 .../man/{Labels.c.3o => Labels.class-c.3o} | 0 ...d.inherits.3o => Nested.class-inherits.3o} | 0 .../man/{Nested.z.3o => Nested.class-z.3o} | 0 ....X.Y.c.3o => Ocamlary.Dep1.X.Y.class-c.3o} | 0 ...y.Dep13.c.3o => Ocamlary.Dep13.class-c.3o} | 0 ...class.3o => Ocamlary.class-empty_class.3o} | 0 ....3o => Ocamlary.class-one_method_class.3o} | 0 ...class.3o => Ocamlary.class-param_class.3o} | 0 ....3o => Ocamlary.class-two_method_class.3o} | 0 ...ts.c1.3o => Toplevel_comments.class-c1.3o} | 0 ...ts.c2.3o => Toplevel_comments.class-c2.3o} | 0 test/generators/man/bugs_post_406.targets | 2 +- test/generators/man/class.targets | 8 +- test/generators/man/class_comments.targets | 4 +- test/generators/man/labels.targets | 2 +- test/generators/man/nested.targets | 4 +- test/generators/man/ocamlary.targets | 12 +- test/generators/man/toplevel_comments.targets | 4 +- test/xref2/github_issue_857.t/run.t | 4 +- test/xref2/map_ref_to_url.t/run.t | 2 +- 114 files changed, 1012 insertions(+), 1001 deletions(-) rename test/generators/man/{Bugs_post_406.let_open'.3o => Bugs_post_406.class-let_open'.3o} (100%) rename test/generators/man/{Class.empty_virtual'.3o => Class.class-empty_virtual'.3o} (100%) rename test/generators/man/{Class.mutually'.3o => Class.class-mutually'.3o} (100%) rename test/generators/man/{Class.polymorphic'.3o => Class.class-polymorphic'.3o} (100%) rename test/generators/man/{Class.recursive'.3o => Class.class-recursive'.3o} (100%) rename test/generators/man/{Class_comments.c.3o => Class_comments.class-c.3o} (100%) rename test/generators/man/{Class_comments.x.3o => Class_comments.class-x.3o} (100%) rename test/generators/man/{Labels.c.3o => Labels.class-c.3o} (100%) rename test/generators/man/{Nested.inherits.3o => Nested.class-inherits.3o} (100%) rename test/generators/man/{Nested.z.3o => Nested.class-z.3o} (100%) rename test/generators/man/{Ocamlary.Dep1.X.Y.c.3o => Ocamlary.Dep1.X.Y.class-c.3o} (100%) rename test/generators/man/{Ocamlary.Dep13.c.3o => Ocamlary.Dep13.class-c.3o} (100%) rename test/generators/man/{Ocamlary.empty_class.3o => Ocamlary.class-empty_class.3o} (100%) rename test/generators/man/{Ocamlary.one_method_class.3o => Ocamlary.class-one_method_class.3o} (100%) rename test/generators/man/{Ocamlary.param_class.3o => Ocamlary.class-param_class.3o} (100%) rename test/generators/man/{Ocamlary.two_method_class.3o => Ocamlary.class-two_method_class.3o} (100%) rename test/generators/man/{Toplevel_comments.c1.3o => Toplevel_comments.class-c1.3o} (100%) rename test/generators/man/{Toplevel_comments.c2.3o => Toplevel_comments.class-c2.3o} (100%) diff --git a/src/document/url.ml b/src/document/url.ml index 0da0579174..0e4bfb01ac 100644 --- a/src/document/url.ml +++ b/src/document/url.ml @@ -115,6 +115,10 @@ module Path = struct let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind) + let pp_kind_prefix_for_output fmt = function + | `Module | `Page | `LeafPage | `File | `SourcePage -> () + | kind -> Format.fprintf fmt "%s-" (string_of_kind kind) + type t = { kind : kind; parent : t option; name : string } let mk ?parent kind name = { kind; parent; name } diff --git a/src/document/url.mli b/src/document/url.mli index 05736d6512..2b13e4de8e 100644 --- a/src/document/url.mli +++ b/src/document/url.mli @@ -27,6 +27,9 @@ module Path : sig val string_of_kind : kind -> string + val pp_kind_prefix_for_output : Format.formatter -> kind -> unit + (** Print the ["kind-"] prefix used in output files. *) + type t = { kind : kind; parent : t option; name : string } type any_pv = diff --git a/src/html/link.ml b/src/html/link.ml index 871bcc12df..dba7b7d3d9 100644 --- a/src/html/link.ml +++ b/src/html/link.ml @@ -5,9 +5,7 @@ module Path = struct let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = - match kind with - | `Module | `Page | `File | `SourcePage -> name - | _ -> Format.asprintf "%a-%s" Url.Path.pp_kind kind name + Format.asprintf "%a%s" Url.Path.pp_kind_prefix_for_output kind name let is_leaf_page url = url.Url.Path.kind = `LeafPage diff --git a/src/latex/generator.ml b/src/latex/generator.ml index 470edec96d..0ba76c2f8f 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -1,14 +1,16 @@ open Odoc_document.Types open Types module Doctree = Odoc_document.Doctree +module Url = Odoc_document.Url module Link = struct let rec flatten_path ppf (x : Odoc_document.Url.Path.t) = - match x.parent with - | Some p -> - Fmt.pf ppf "%a-%a-%s" flatten_path p Odoc_document.Url.Path.pp_kind - x.kind x.name - | None -> Fmt.pf ppf "%a-%s" Odoc_document.Url.Path.pp_kind x.kind x.name + let pp_parent ppf = function + | Some p -> Format.fprintf ppf "%a-" flatten_path p + | None -> () + in + Format.fprintf ppf "%a%a%s" pp_parent x.parent + Url.Path.pp_kind_prefix_for_output x.kind x.name let page p = Format.asprintf "%a" flatten_path p diff --git a/src/manpage/link.ml b/src/manpage/link.ml index f007aa5510..3fd606b29e 100644 --- a/src/manpage/link.ml +++ b/src/manpage/link.ml @@ -3,9 +3,7 @@ open Odoc_document let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = - match kind with - | `Module | `Page | `LeafPage | `Class -> name - | _ -> Format.asprintf "%a-%s" Odoc_document.Url.Path.pp_kind kind name + Format.asprintf "%a%s" Url.Path.pp_kind_prefix_for_output kind name let as_filename ?(add_ext = true) (url : Url.Path.t) = let components = Url.Path.to_list url in diff --git a/test/generators/latex/Alerts.tex b/test/generators/latex/Alerts.tex index 01ef0e0ac9..761fc09405 100644 --- a/test/generators/latex/Alerts.tex +++ b/test/generators/latex/Alerts.tex @@ -1,41 +1,41 @@ -\section{Module \ocamlinlinecode{Alerts}}\label{module-Alerts}% -\label{module-Alerts-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\section{Module \ocamlinlinecode{Alerts}}\label{Alerts}% +\label{Alerts-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{deprecated}]{a}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Alerts-val-b}\ocamlcodefragment{\ocamltag{keyword}{val} b : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Alerts-val-b}\ocamlcodefragment{\ocamltag{keyword}{val} b : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{deprecated}]{b.}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Alerts-val-c}\ocamlcodefragment{\ocamltag{keyword}{val} c : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Alerts-val-c}\ocamlcodefragment{\ocamltag{keyword}{val} c : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{deprecated}]{}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Alerts-module-Top1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Alerts-module-Top1]{\ocamlinlinecode{Top1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Alerts-module-Top1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Alerts-Top1]{\ocamlinlinecode{Top1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment.\end{ocamlindent}% \medbreak -\label{module-Alerts-module-Top2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Alerts-module-Top2]{\ocamlinlinecode{Top2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Alerts-module-Top2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Alerts-Top2]{\ocamlinlinecode{Top2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment.\end{ocamlindent}% \medbreak -\label{module-Alerts-val-d}\ocamlcodefragment{\ocamltag{keyword}{val} d : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Alerts-val-d}\ocamlcodefragment{\ocamltag{keyword}{val} d : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{deprecated}]{A deprecated alert d}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Alerts-val-d2}\ocamlcodefragment{\ocamltag{keyword}{val} d2 : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Alerts-val-d2}\ocamlcodefragment{\ocamltag{keyword}{val} d2 : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{deprecated}]{}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Alerts-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Alerts-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{alert}]{e an alert}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Alerts-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : int}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Alerts-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : int}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{alert}]{f}\end{description}% \end{ocamlindent}% diff --git a/test/generators/latex/Alias.X.tex b/test/generators/latex/Alias.X.tex index df11cbc727..00e1e70521 100644 --- a/test/generators/latex/Alias.X.tex +++ b/test/generators/latex/Alias.X.tex @@ -1,5 +1,5 @@ -\section{Module \ocamlinlinecode{Alias.\allowbreak{}X}}\label{module-Alias-module-X}% -\label{module-Alias-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}% +\section{Module \ocamlinlinecode{Alias.\allowbreak{}X}}\label{Alias-X}% +\label{Alias-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Alias.tex b/test/generators/latex/Alias.tex index f506a06d9e..cd9ef6a1c9 100644 --- a/test/generators/latex/Alias.tex +++ b/test/generators/latex/Alias.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Alias}}\label{module-Alias}% -\label{module-Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Alias-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\section{Module \ocamlinlinecode{Alias}}\label{Alias}% +\label{Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Alias-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Alias.X.tex} diff --git a/test/generators/latex/Bugs.tex b/test/generators/latex/Bugs.tex index 1a25322cf2..918325cd4a 100644 --- a/test/generators/latex/Bugs.tex +++ b/test/generators/latex/Bugs.tex @@ -1,8 +1,8 @@ -\section{Module \ocamlinlinecode{Bugs}}\label{module-Bugs}% -\label{module-Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\ -\label{module-Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : \ocamltag{optlabel}{?bar}:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}% +\section{Module \ocamlinlinecode{Bugs}}\label{Bugs}% +\label{Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\ +\label{Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : \ocamltag{optlabel}{?bar}:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}% \medbreak -\label{module-Bugs-val-repeat}\ocamlcodefragment{\ocamltag{keyword}{val} repeat : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} * \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b}}\begin{ocamlindent}Renders as \ocamlinlinecode{val repeat : 'a -> 'b -> 'c * 'd * 'e * 'f} before https://github.com/ocaml/odoc/pull/1173\end{ocamlindent}% +\label{Bugs-val-repeat}\ocamlcodefragment{\ocamltag{keyword}{val} repeat : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} * \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b}}\begin{ocamlindent}Renders as \ocamlinlinecode{val repeat : 'a -> 'b -> 'c * 'd * 'e * 'f} before https://github.com/ocaml/odoc/pull/1173\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Bugs_post_406.let_open'.tex b/test/generators/latex/Bugs_post_406.let_open'.tex index f4e3a325dd..4faf350762 100644 --- a/test/generators/latex/Bugs_post_406.let_open'.tex +++ b/test/generators/latex/Bugs_post_406.let_open'.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406.\allowbreak{}let\_\allowbreak{}open'}}\label{module-Bugs_post_406-class-let_open'}% +\section{Class \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406.\allowbreak{}let\_\allowbreak{}open'}}\label{Bugs_post_406-class-let_open'}% diff --git a/test/generators/latex/Bugs_post_406.tex b/test/generators/latex/Bugs_post_406.tex index 61bacf5397..20f3806ad9 100644 --- a/test/generators/latex/Bugs_post_406.tex +++ b/test/generators/latex/Bugs_post_406.tex @@ -1,8 +1,8 @@ -\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406}}\label{module-Bugs_post_406}% +\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406}}\label{Bugs_post_406}% Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 -\label{module-Bugs_post_406-class-type-let_open}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Bugs_post_406-class-type-let_open]{\ocamlinlinecode{let\_\allowbreak{}open}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{Bugs_post_406-class-type-let_open}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[Bugs_post_406-class-type-let_open]{\ocamlinlinecode{let\_\allowbreak{}open}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Bugs_post_406-class-let_open'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Bugs_post_406-class-let_open']{\ocamlinlinecode{let\_\allowbreak{}open'}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Bugs_post_406-class-let_open'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Bugs_post_406-class-let_open']{\ocamlinlinecode{let\_\allowbreak{}open'}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Bugs_post_406.let_open'.tex} diff --git a/test/generators/latex/Bugs_pre_410.tex b/test/generators/latex/Bugs_pre_410.tex index 4f9128ed75..a20e294173 100644 --- a/test/generators/latex/Bugs_pre_410.tex +++ b/test/generators/latex/Bugs_pre_410.tex @@ -1,6 +1,6 @@ -\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}pre\_\allowbreak{}410}}\label{module-Bugs_pre_410}% -\label{module-Bugs_pre_410-type-opt'}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt' = int option}\\ -\label{module-Bugs_pre_410-val-foo'}\ocamlcodefragment{\ocamltag{keyword}{val} foo' : \ocamltag{optlabel}{?bar}:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Similar to \ocamlinlinecode{Bugs}, but the printed type of \ocamlinlinecode{\textasciitilde{}bar} should be \ocamlinlinecode{int}, not \ocamlinlinecode{'a}. This probably requires fixing in the compiler. See \href{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}\footnote{\url{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}}.\end{ocamlindent}% +\section{Module \ocamlinlinecode{Bugs\_\allowbreak{}pre\_\allowbreak{}410}}\label{Bugs_pre_410}% +\label{Bugs_pre_410-type-opt'}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt' = int option}\\ +\label{Bugs_pre_410-val-foo'}\ocamlcodefragment{\ocamltag{keyword}{val} foo' : \ocamltag{optlabel}{?bar}:\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Similar to \ocamlinlinecode{Bugs}, but the printed type of \ocamlinlinecode{\textasciitilde{}bar} should be \ocamlinlinecode{int}, not \ocamlinlinecode{'a}. This probably requires fixing in the compiler. See \href{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}\footnote{\url{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}}.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Class.empty_virtual'.tex b/test/generators/latex/Class.empty_virtual'.tex index ba20ae55ee..5bad918e86 100644 --- a/test/generators/latex/Class.empty_virtual'.tex +++ b/test/generators/latex/Class.empty_virtual'.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Class.\allowbreak{}empty\_\allowbreak{}virtual'}}\label{module-Class-class-empty_virtual'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}empty\_\allowbreak{}virtual'}}\label{Class-class-empty_virtual'}% diff --git a/test/generators/latex/Class.mutually'.tex b/test/generators/latex/Class.mutually'.tex index 82677b8a61..b36a3762e1 100644 --- a/test/generators/latex/Class.mutually'.tex +++ b/test/generators/latex/Class.mutually'.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Class.\allowbreak{}mutually'}}\label{module-Class-class-mutually'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}mutually'}}\label{Class-class-mutually'}% diff --git a/test/generators/latex/Class.polymorphic'.tex b/test/generators/latex/Class.polymorphic'.tex index 0545c384f9..9fdb29ee6c 100644 --- a/test/generators/latex/Class.polymorphic'.tex +++ b/test/generators/latex/Class.polymorphic'.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Class.\allowbreak{}polymorphic'}}\label{module-Class-class-polymorphic'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}polymorphic'}}\label{Class-class-polymorphic'}% diff --git a/test/generators/latex/Class.recursive'.tex b/test/generators/latex/Class.recursive'.tex index 5c924ffd06..15e19a54d4 100644 --- a/test/generators/latex/Class.recursive'.tex +++ b/test/generators/latex/Class.recursive'.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Class.\allowbreak{}recursive'}}\label{module-Class-class-recursive'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}recursive'}}\label{Class-class-recursive'}% diff --git a/test/generators/latex/Class.tex b/test/generators/latex/Class.tex index 17da90b6e5..6ed810fff8 100644 --- a/test/generators/latex/Class.tex +++ b/test/generators/latex/Class.tex @@ -1,18 +1,18 @@ -\section{Module \ocamlinlinecode{Class}}\label{module-Class}% -\label{module-Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\section{Module \ocamlinlinecode{Class}}\label{Class}% +\label{Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\ -\label{module-Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\ -\label{module-Class-class-type-empty_virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[module-Class-class-type-empty_virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\ +\label{Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\ +\label{Class-class-type-empty_virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[Class-class-type-empty_virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-empty_virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Class-class-empty_virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\\ -\label{module-Class-class-type-polymorphic}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} 'a \hyperref[module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{Class-class-empty_virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[Class-class-empty_virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[Class-class-type-empty]{\ocamlinlinecode{empty}}}\\ +\label{Class-class-type-polymorphic}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} 'a \hyperref[Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-polymorphic'}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[module-Class-class-polymorphic']{\ocamlinlinecode{polymorphic'}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \hyperref[module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\\ +\label{Class-class-polymorphic'}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[Class-class-polymorphic']{\ocamlinlinecode{polymorphic'}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \hyperref[Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\\ \input{Class.mutually'.tex} \input{Class.recursive'.tex} diff --git a/test/generators/latex/Class_comments.c.tex b/test/generators/latex/Class_comments.c.tex index 6ae3958fda..a9c9c02bfc 100644 --- a/test/generators/latex/Class_comments.c.tex +++ b/test/generators/latex/Class_comments.c.tex @@ -1,10 +1,10 @@ -\section{Class \ocamlinlinecode{Class\_\allowbreak{}comments.\allowbreak{}c}}\label{module-Class_comments-class-c}% -\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[module-Class_comments-class-x]{\ocamlinlinecode{x}}}\begin{ocamlindent}Inherit.\end{ocamlindent}% +\section{Class \ocamlinlinecode{Class\_\allowbreak{}comments.\allowbreak{}c}}\label{Class_comments-class-c}% +\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[Class_comments-class-x]{\ocamlinlinecode{x}}}\begin{ocamlindent}Inherit.\end{ocamlindent}% \medbreak \ocamlcodefragment{ \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int}\begin{ocamlindent}Constraint.\end{ocamlindent}% \medbreak Floating comment. -\label{module-Class_comments-class-c-method-bar}\ocamlcodefragment{\ocamltag{keyword}{method} bar : int}\\ +\label{Class_comments-class-c-method-bar}\ocamlcodefragment{\ocamltag{keyword}{method} bar : int}\\ diff --git a/test/generators/latex/Class_comments.tex b/test/generators/latex/Class_comments.tex index 079b2d5526..bf9ad6a97f 100644 --- a/test/generators/latex/Class_comments.tex +++ b/test/generators/latex/Class_comments.tex @@ -1,6 +1,6 @@ -\section{Module \ocamlinlinecode{Class\_\allowbreak{}comments}}\label{module-Class_comments}% -\label{module-Class_comments-class-x}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class_comments-class-x]{\ocamlinlinecode{x}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Class_comments-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[module-Class_comments-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\section{Module \ocamlinlinecode{Class\_\allowbreak{}comments}}\label{Class_comments}% +\label{Class_comments-class-x}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Class_comments-class-x]{\ocamlinlinecode{x}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Class_comments-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[Class_comments-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Class_comments.x.tex} \input{Class_comments.c.tex} diff --git a/test/generators/latex/Class_comments.x.tex b/test/generators/latex/Class_comments.x.tex index 633ac2c40e..b1eed585e7 100644 --- a/test/generators/latex/Class_comments.x.tex +++ b/test/generators/latex/Class_comments.x.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Class\_\allowbreak{}comments.\allowbreak{}x}}\label{module-Class_comments-class-x}% +\section{Class \ocamlinlinecode{Class\_\allowbreak{}comments.\allowbreak{}x}}\label{Class_comments-class-x}% diff --git a/test/generators/latex/External.tex b/test/generators/latex/External.tex index 795e00d8ff..8a533609d7 100644 --- a/test/generators/latex/External.tex +++ b/test/generators/latex/External.tex @@ -1,5 +1,5 @@ -\section{Module \ocamlinlinecode{External}}\label{module-External}% -\label{module-External-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Foo \emph{bar}.\end{ocamlindent}% +\section{Module \ocamlinlinecode{External}}\label{External}% +\label{External-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Foo \emph{bar}.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Functor.F1.tex b/test/generators/latex/Functor.F1.tex index 3777b02940..080bd453d2 100644 --- a/test/generators/latex/Functor.F1.tex +++ b/test/generators/latex/Functor.F1.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Functor.\allowbreak{}F1}}\label{module-Functor-module-F1}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F1}}\label{Functor-F1}% \subsection{Parameters\label{parameters}}% -\label{module-Functor-module-F1-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor-module-F1-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F1-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F1-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor-F1-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Functor-module-F1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/generators/latex/Functor.F2.tex b/test/generators/latex/Functor.F2.tex index b303684338..b430dea684 100644 --- a/test/generators/latex/Functor.F2.tex +++ b/test/generators/latex/Functor.F2.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Functor.\allowbreak{}F2}}\label{module-Functor-module-F2}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F2}}\label{Functor-F2}% \subsection{Parameters\label{parameters}}% -\label{module-Functor-module-F2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor-module-F2-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor-F2-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Functor-module-F2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ +\label{Functor-F2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Functor-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ diff --git a/test/generators/latex/Functor.F3.tex b/test/generators/latex/Functor.F3.tex index b0bd3e0c99..a65e336e88 100644 --- a/test/generators/latex/Functor.F3.tex +++ b/test/generators/latex/Functor.F3.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Functor.\allowbreak{}F3}}\label{module-Functor-module-F3}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F3}}\label{Functor-F3}% \subsection{Parameters\label{parameters}}% -\label{module-Functor-module-F3-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor-module-F3-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F3-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F3-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor-F3-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Functor-module-F3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Functor-module-F3-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ +\label{Functor-F3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Functor-F3-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ diff --git a/test/generators/latex/Functor.F4.tex b/test/generators/latex/Functor.F4.tex index 9cd87ffd3e..c259c01ce1 100644 --- a/test/generators/latex/Functor.F4.tex +++ b/test/generators/latex/Functor.F4.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Functor.\allowbreak{}F4}}\label{module-Functor-module-F4}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F4}}\label{Functor-F4}% \subsection{Parameters\label{parameters}}% -\label{module-Functor-module-F4-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor-module-F4-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F4-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F4-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor-F4-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Functor-module-F4-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F4-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/generators/latex/Functor.F5.tex b/test/generators/latex/Functor.F5.tex index d0adb0595a..577a715499 100644 --- a/test/generators/latex/Functor.F5.tex +++ b/test/generators/latex/Functor.F5.tex @@ -1,6 +1,6 @@ -\section{Module \ocamlinlinecode{Functor.\allowbreak{}F5}}\label{module-Functor-module-F5}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F5}}\label{Functor-F5}% \subsection{Parameters\label{parameters}}% \subsection{Signature\label{signature}}% -\label{module-Functor-module-F5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-F5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/generators/latex/Functor.tex b/test/generators/latex/Functor.tex index b63d00948b..349a1890d1 100644 --- a/test/generators/latex/Functor.tex +++ b/test/generators/latex/Functor.tex @@ -1,20 +1,20 @@ -\section{Module \ocamlinlinecode{Functor}}\label{module-Functor}% -\label{module-Functor-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Functor}}\label{Functor}% +\label{Functor-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Functor-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Functor-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{module-Functor-module-type-S1-argument-1-_}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-type-S1-argument-1-_]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor-module-type-S1-argument-1-_-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Functor-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{Functor-module-type-S1-argument-1-_}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-module-type-S1-argument-1-_]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor-module-type-S1-argument-1-_-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% -\label{module-Functor-module-type-S1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor-module-type-S1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Functor-module-F1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F1]{\ocamlinlinecode{F1}}}\ocamlcodefragment{ (\hyperref[module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\ -\label{module-Functor-module-F2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F2]{\ocamlinlinecode{F2}}}\ocamlcodefragment{ (\hyperref[module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[module-Functor-module-type-S-type-t]{\ocamlinlinecode{t}} = \hyperref[module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ -\label{module-Functor-module-F3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F3]{\ocamlinlinecode{F3}}}\ocamlcodefragment{ (\hyperref[module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Functor-module-F4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F4]{\ocamlinlinecode{F4}}}\ocamlcodefragment{ (\hyperref[module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\ -\label{module-Functor-module-F5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor-module-F5]{\ocamlinlinecode{F5}}}\ocamlcodefragment{ () : \hyperref[module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Functor-module-F1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F1]{\ocamlinlinecode{F1}}}\ocamlcodefragment{ (\hyperref[Functor-F1-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Functor-module-F2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F2]{\ocamlinlinecode{F2}}}\ocamlcodefragment{ (\hyperref[Functor-F2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[Functor-module-type-S-type-t]{\ocamlinlinecode{t}} = \hyperref[Functor-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ +\label{Functor-module-F3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F3]{\ocamlinlinecode{F3}}}\ocamlcodefragment{ (\hyperref[Functor-F3-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Functor-module-F4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F4]{\ocamlinlinecode{F4}}}\ocamlcodefragment{ (\hyperref[Functor-F4-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Functor-module-F5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor-F5]{\ocamlinlinecode{F5}}}\ocamlcodefragment{ () : \hyperref[Functor-module-type-S]{\ocamlinlinecode{S}}}\\ \input{Functor.F1.tex} \input{Functor.F2.tex} diff --git a/test/generators/latex/Functor2.X.tex b/test/generators/latex/Functor2.X.tex index 25cb9d3055..884600afa4 100644 --- a/test/generators/latex/Functor2.X.tex +++ b/test/generators/latex/Functor2.X.tex @@ -1,14 +1,14 @@ -\section{Module \ocamlinlinecode{Functor2.\allowbreak{}X}}\label{module-Functor2-module-X}% +\section{Module \ocamlinlinecode{Functor2.\allowbreak{}X}}\label{Functor2-X}% \subsection{Parameters\label{parameters}}% -\label{module-Functor2-module-X-argument-1-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor2-module-X-argument-1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor2-module-X-argument-1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor2-X-argument-1-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor2-X-argument-1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor2-X-argument-1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Functor2-module-X-argument-2-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor2-module-X-argument-2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor2-module-X-argument-2-Z-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor2-X-argument-2-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor2-X-argument-2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor2-X-argument-2-Z-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Functor2-module-X-type-y_t}\ocamlcodefragment{\ocamltag{keyword}{type} y\_\allowbreak{}t = \hyperref[module-Functor2-module-X-argument-1-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ -\label{module-Functor2-module-X-type-z_t}\ocamlcodefragment{\ocamltag{keyword}{type} z\_\allowbreak{}t = \hyperref[module-Functor2-module-X-argument-2-Z-type-t]{\ocamlinlinecode{Z.\allowbreak{}t}}}\\ -\label{module-Functor2-module-X-type-x_t}\ocamlcodefragment{\ocamltag{keyword}{type} x\_\allowbreak{}t = \hyperref[module-Functor2-module-X-type-y_t]{\ocamlinlinecode{y\_\allowbreak{}t}}}\\ +\label{Functor2-X-type-y_t}\ocamlcodefragment{\ocamltag{keyword}{type} y\_\allowbreak{}t = \hyperref[Functor2-X-argument-1-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ +\label{Functor2-X-type-z_t}\ocamlcodefragment{\ocamltag{keyword}{type} z\_\allowbreak{}t = \hyperref[Functor2-X-argument-2-Z-type-t]{\ocamlinlinecode{Z.\allowbreak{}t}}}\\ +\label{Functor2-X-type-x_t}\ocamlcodefragment{\ocamltag{keyword}{type} x\_\allowbreak{}t = \hyperref[Functor2-X-type-y_t]{\ocamlinlinecode{y\_\allowbreak{}t}}}\\ diff --git a/test/generators/latex/Functor2.tex b/test/generators/latex/Functor2.tex index 88c7f6c810..8a3b8c40ef 100644 --- a/test/generators/latex/Functor2.tex +++ b/test/generators/latex/Functor2.tex @@ -1,19 +1,19 @@ -\section{Module \ocamlinlinecode{Functor2}}\label{module-Functor2}% -\label{module-Functor2-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Functor2-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor2-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Functor2}}\label{Functor2}% +\label{Functor2-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Functor2-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor2-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Functor2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor2-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ (\hyperref[module-Functor2-module-X-argument-1-Y]{\ocamlinlinecode{Y}} : \hyperref[module-Functor2-module-type-S]{\ocamlinlinecode{S}}) (\hyperref[module-Functor2-module-X-argument-2-Z]{\ocamlinlinecode{Z}} : \hyperref[module-Functor2-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Functor2-module-type-XF}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Functor2-module-type-XF]{\ocamlinlinecode{XF}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters_2}}% -\label{module-Functor2-module-type-XF-argument-1-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor2-module-type-XF-argument-1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor2-module-type-XF-argument-1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor2-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ (\hyperref[Functor2-X-argument-1-Y]{\ocamlinlinecode{Y}} : \hyperref[Functor2-module-type-S]{\ocamlinlinecode{S}}) (\hyperref[Functor2-X-argument-2-Z]{\ocamlinlinecode{Z}} : \hyperref[Functor2-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Functor2-module-type-XF}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Functor2-module-type-XF]{\ocamlinlinecode{XF}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters_2}}% +\label{Functor2-module-type-XF-argument-1-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor2-module-type-XF-argument-1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor2-module-type-XF-argument-1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Functor2-module-type-XF-argument-2-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor2-module-type-XF-argument-2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor2-module-type-XF-argument-2-Z-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Functor2-module-type-XF-argument-2-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor2-module-type-XF-argument-2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor2-module-type-XF-argument-2-Z-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature_2}}% -\label{module-Functor2-module-type-XF-type-y_t}\ocamlcodefragment{\ocamltag{keyword}{type} y\_\allowbreak{}t = \hyperref[module-Functor2-module-type-XF-argument-1-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ -\label{module-Functor2-module-type-XF-type-z_t}\ocamlcodefragment{\ocamltag{keyword}{type} z\_\allowbreak{}t = \hyperref[module-Functor2-module-type-XF-argument-2-Z-type-t]{\ocamlinlinecode{Z.\allowbreak{}t}}}\\ -\label{module-Functor2-module-type-XF-type-x_t}\ocamlcodefragment{\ocamltag{keyword}{type} x\_\allowbreak{}t = \hyperref[module-Functor2-module-type-XF-type-y_t]{\ocamlinlinecode{y\_\allowbreak{}t}}}\\ +\label{Functor2-module-type-XF-type-y_t}\ocamlcodefragment{\ocamltag{keyword}{type} y\_\allowbreak{}t = \hyperref[Functor2-module-type-XF-argument-1-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ +\label{Functor2-module-type-XF-type-z_t}\ocamlcodefragment{\ocamltag{keyword}{type} z\_\allowbreak{}t = \hyperref[Functor2-module-type-XF-argument-2-Z-type-t]{\ocamlinlinecode{Z.\allowbreak{}t}}}\\ +\label{Functor2-module-type-XF-type-x_t}\ocamlcodefragment{\ocamltag{keyword}{type} x\_\allowbreak{}t = \hyperref[Functor2-module-type-XF-type-y_t]{\ocamlinlinecode{y\_\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/generators/latex/Functor_ml.Foo'.tex b/test/generators/latex/Functor_ml.Foo'.tex index 01a894844d..b8e00dd732 100644 --- a/test/generators/latex/Functor_ml.Foo'.tex +++ b/test/generators/latex/Functor_ml.Foo'.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Functor\_\allowbreak{}ml.\allowbreak{}Foo'}}\label{module-Functor_ml-module-Foo'}% +\section{Module \ocamlinlinecode{Functor\_\allowbreak{}ml.\allowbreak{}Foo'}}\label{Functor_ml-Foo'}% \subsection{Parameters\label{parameters}}% -\label{module-Functor_ml-module-Foo'-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor_ml-module-Foo'-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor_ml-module-Foo'-argument-1-X-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\\ +\label{Functor_ml-Foo'-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor_ml-Foo'-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor_ml-Foo'-argument-1-X-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Functor_ml-module-Foo'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Functor_ml-module-Bar-type-t]{\ocamlinlinecode{Bar.\allowbreak{}t}}}\\ +\label{Functor_ml-Foo'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Functor_ml-Bar-type-t]{\ocamlinlinecode{Bar.\allowbreak{}t}}}\\ diff --git a/test/generators/latex/Functor_ml.tex b/test/generators/latex/Functor_ml.tex index 963899c9ec..463d91c45d 100644 --- a/test/generators/latex/Functor_ml.tex +++ b/test/generators/latex/Functor_ml.tex @@ -1,8 +1,8 @@ -\section{Module \ocamlinlinecode{Functor\_\allowbreak{}ml}}\label{module-Functor_ml}% -\label{module-Functor_ml-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} Foo (\hyperref[module-Functor_ml-module-Foo-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Stdlib}}.\allowbreak{}String}\\ -\label{module-Functor_ml-module-Bar}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor_ml-module-Bar]{\ocamlinlinecode{Bar}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Functor_ml-module-Bar-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Functor\_\allowbreak{}ml}}\label{Functor_ml}% +\label{Functor_ml-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} Foo (\hyperref[Functor_ml-Foo-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Stdlib}}.\allowbreak{}String}\\ +\label{Functor_ml-module-Bar}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor_ml-Bar]{\ocamlinlinecode{Bar}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Functor_ml-Bar-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Functor_ml-module-Foo'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Functor_ml-module-Foo']{\ocamlinlinecode{Foo'}}}\ocamlcodefragment{ (\hyperref[module-Functor_ml-module-Foo'-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Functor_ml-module-Foo'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Functor_ml-Foo']{\ocamlinlinecode{Foo'}}}\ocamlcodefragment{ (\hyperref[Functor_ml-Foo'-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Functor_ml.Foo'.tex} diff --git a/test/generators/latex/Include.tex b/test/generators/latex/Include.tex index 393fcc5b2f..0129504c88 100644 --- a/test/generators/latex/Include.tex +++ b/test/generators/latex/Include.tex @@ -1,26 +1,26 @@ -\section{Module \ocamlinlinecode{Include}}\label{module-Include}% -\label{module-Include-module-type-Not_inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include-module-type-Not_inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include-module-type-Not_inlined-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Include}}\label{Include}% +\label{Include-module-type-Not_inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include-module-type-Not_inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include-module-type-Not_inlined-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Not_inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}\label{module-Include-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Include-module-type-Inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include-module-type-Inlined-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\ocamltag{keyword}{include} \hyperref[Include-module-type-Not_inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}\label{Include-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Include-module-type-Inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include-module-type-Inlined-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}\label{module-Include-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Include-module-type-Not_inlined_and_closed}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include-module-type-Not_inlined_and_closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include-module-type-Not_inlined_and_closed-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\ +\ocamltag{keyword}{include} \hyperref[Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}\label{Include-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Include-module-type-Not_inlined_and_closed}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include-module-type-Not_inlined_and_closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include-module-type-Not_inlined_and_closed-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Not_inlined_and_closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}\label{module-Include-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\ -\label{module-Include-module-type-Not_inlined_and_opened}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include-module-type-Not_inlined_and_opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include-module-type-Not_inlined_and_opened-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\ +\ocamltag{keyword}{include} \hyperref[Include-module-type-Not_inlined_and_closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}\label{Include-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\ +\label{Include-module-type-Not_inlined_and_opened}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include-module-type-Not_inlined_and_opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include-module-type-Not_inlined_and_opened-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Not_inlined_and_opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}\label{module-Include-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\ -\label{module-Include-module-type-Inherent_Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include-module-type-Inherent_Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[module-Include-type-t]{\ocamlinlinecode{t}}}\\ +\ocamltag{keyword}{include} \hyperref[Include-module-type-Not_inlined_and_opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}\label{Include-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\ +\label{Include-module-type-Inherent_Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include-module-type-Inherent_Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[Include-type-t]{\ocamlinlinecode{t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{module-Include-module-type-Dorminant_Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include-module-type-Dorminant_Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{module-Include-module-type-Dorminant_Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[module-Include-type-u]{\ocamlinlinecode{u}}}\\ +\ocamltag{keyword}{include} \hyperref[Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{Include-module-type-Dorminant_Module}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include-module-type-Dorminant_Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{Include-module-type-Dorminant_Module-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[Include-type-u]{\ocamlinlinecode{u}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Dorminant_Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}\ocamltag{keyword}{include} \hyperref[module-Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{module-Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[module-Include-type-u]{\ocamlinlinecode{u}}}\\ +\ocamltag{keyword}{include} \hyperref[Include-module-type-Dorminant_Module]{\ocamlinlinecode{Dorminant\_\allowbreak{}Module}}\ocamltag{keyword}{include} \hyperref[Include-module-type-Inherent_Module]{\ocamlinlinecode{Inherent\_\allowbreak{}Module}}\label{Include-val-a}\ocamlcodefragment{\ocamltag{keyword}{val} a : \hyperref[Include-type-u]{\ocamlinlinecode{u}}}\\ diff --git a/test/generators/latex/Include2.tex b/test/generators/latex/Include2.tex index da62fe9b78..bd039c8c14 100644 --- a/test/generators/latex/Include2.tex +++ b/test/generators/latex/Include2.tex @@ -1,18 +1,18 @@ -\section{Module \ocamlinlinecode{Include2}}\label{module-Include2}% -\label{module-Include2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Include2-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include2-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ +\section{Module \ocamlinlinecode{Include2}}\label{Include2}% +\label{Include2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Include2-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include2-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Comment about X that should not appear when including X below.\end{ocamlindent}% \medbreak -\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[module-Include2-module-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{end}\label{module-Include2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ -\label{module-Include2-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Include2-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include2-module-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[Include2-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{end}\label{Include2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ +\label{Include2-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Include2-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include2-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Top-comment of Y.\end{ocamlindent}% \medbreak -\label{module-Include2-module-Y_include_synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Include2-module-Y_include_synopsis]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[module-Include2-module-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{module-Include2-module-Y_include_synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Include2-module-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ +\label{Include2-module-Y_include_synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Include2-Y_include_synopsis]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[Include2-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{Include2-Y_include_synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Include2-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}The \ocamlinlinecode{include Y} below should have the synopsis from \ocamlinlinecode{Y}'s top-comment attached to it.\end{ocamlindent}% \medbreak -\label{module-Include2-module-Y_include_doc}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Include2-module-Y_include_doc]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}doc}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}Doc attached to \ocamlinlinecode{include Y}. \ocamlinlinecode{Y}'s top-comment shouldn't appear here.\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[module-Include2-module-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{module-Include2-module-Y_include_doc-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Include2-module-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ +\label{Include2-module-Y_include_doc}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Include2-Y_include_doc]{\ocamlinlinecode{Y\_\allowbreak{}include\_\allowbreak{}doc}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}Doc attached to \ocamlinlinecode{include Y}. \ocamlinlinecode{Y}'s top-comment shouldn't appear here.\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[Include2-Y]{\ocamlinlinecode{Y}} \ocamltag{keyword}{end}\label{Include2-Y_include_doc-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Include2-Y-type-t]{\ocamlinlinecode{Y.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/generators/latex/Include_sections.tex b/test/generators/latex/Include_sections.tex index 98b2bdf97e..b87537b154 100644 --- a/test/generators/latex/Include_sections.tex +++ b/test/generators/latex/Include_sections.tex @@ -1,11 +1,11 @@ -\section{Module \ocamlinlinecode{Include\_\allowbreak{}sections}}\label{module-Include_sections}% -\label{module-Include_sections-module-type-Something}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{Something}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Include_sections-module-type-Something-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ +\section{Module \ocamlinlinecode{Include\_\allowbreak{}sections}}\label{Include_sections}% +\label{Include_sections-module-type-Something}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{Something}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Include_sections-module-type-Something-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsubsection{Something 1\label{something-1}}% foo -\label{module-Include_sections-module-type-Something-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ +\label{Include_sections-module-type-Something-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2}}% -\label{module-Include_sections-module-type-Something-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{Include_sections-module-type-Something-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsubsection{Something 1-bis\label{something-1-bis}}% Some text. @@ -13,9 +13,9 @@ \subsubsection{Something 1-bis\label{something-1-bis}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A module type.\end{ocamlindent}% \medbreak -Let's include \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{module-Include_sections-module-type-Something}]} once +Let's include \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{Include_sections-module-type-Something}]} once -\ocamltag{keyword}{include} \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\subsection{Something 1\label{something-1_2}}% +\ocamltag{keyword}{include} \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\subsection{Something 1\label{something-1_2}}% foo \subsubsection{Something 2\label{something-2_2}}% @@ -23,9 +23,9 @@ \subsection{Something 1-bis\label{something-1-bis_2}}% Some text. \subsection{Second include\label{second-include}}% -Let's include \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{module-Include_sections-module-type-Something}]} a second time: the heading level should be shift here. +Let's include \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{Include_sections-module-type-Something}]} a second time: the heading level should be shift here. -\ocamltag{keyword}{include} \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\subsection{Something 1\label{something-1_3}}% +\ocamltag{keyword}{include} \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\subsection{Something 1\label{something-1_3}}% foo \subsubsection{Something 2\label{something-2_3}}% @@ -35,7 +35,7 @@ \subsection{Something 1-bis\label{something-1-bis_3}}% \subsubsection{Third include\label{third-include}}% Shifted some more. -\ocamltag{keyword}{include} \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\subsection{Something 1\label{something-1_4}}% +\ocamltag{keyword}{include} \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\subsection{Something 1\label{something-1_4}}% foo \subsubsection{Something 2\label{something-2_4}}% @@ -44,13 +44,13 @@ \subsection{Something 1-bis\label{something-1-bis_4}}% And let's include it again, but without inlining it this time: the ToC shouldn't grow. -\ocamltag{keyword}{include} \hyperref[module-Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\label{module-Include_sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ +\ocamltag{keyword}{include} \hyperref[Include_sections-module-type-Something]{\ocamlinlinecode{Something}}\label{Include_sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsection{Something 1\label{something-1_5}}% foo -\label{module-Include_sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ +\label{Include_sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2_5}}% -\label{module-Include_sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{Include_sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsection{Something 1-bis\label{something-1-bis_5}}% Some text. diff --git a/test/generators/latex/Interlude.tex b/test/generators/latex/Interlude.tex index 7a8424dadd..8b180e6969 100644 --- a/test/generators/latex/Interlude.tex +++ b/test/generators/latex/Interlude.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Interlude}}\label{module-Interlude}% +\section{Module \ocamlinlinecode{Interlude}}\label{Interlude}% This is the comment associated to the module. Some separate stray text at the top of the module. -\label{module-Interlude-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% +\label{Interlude-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% \medbreak Some stray text that is not associated with any signature item. @@ -11,11 +11,11 @@ \section{Module \ocamlinlinecode{Interlude}}\label{module-Interlude}% A separate block of stray text, adjacent to the preceding one. -\label{module-Interlude-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% +\label{Interlude-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% \medbreak -\label{module-Interlude-val-multiple}\ocamlcodefragment{\ocamltag{keyword}{val} multiple : unit}\\ -\label{module-Interlude-val-signature}\ocamlcodefragment{\ocamltag{keyword}{val} signature : unit}\\ -\label{module-Interlude-val-items}\ocamlcodefragment{\ocamltag{keyword}{val} items : unit}\\ +\label{Interlude-val-multiple}\ocamlcodefragment{\ocamltag{keyword}{val} multiple : unit}\\ +\label{Interlude-val-signature}\ocamlcodefragment{\ocamltag{keyword}{val} signature : unit}\\ +\label{Interlude-val-items}\ocamlcodefragment{\ocamltag{keyword}{val} items : unit}\\ Stray text at the bottom of the module. diff --git a/test/generators/latex/Labels.c.tex b/test/generators/latex/Labels.c.tex index 097f1f5b3e..9625710713 100644 --- a/test/generators/latex/Labels.c.tex +++ b/test/generators/latex/Labels.c.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Labels.\allowbreak{}c}}\label{module-Labels-class-c}% +\section{Class \ocamlinlinecode{Labels.\allowbreak{}c}}\label{Labels-class-c}% \subsection{Attached to class\label{L7}}% diff --git a/test/generators/latex/Labels.tex b/test/generators/latex/Labels.tex index 0063a18544..033caebd8d 100644 --- a/test/generators/latex/Labels.tex +++ b/test/generators/latex/Labels.tex @@ -1,59 +1,59 @@ -\section{Module \ocamlinlinecode{Labels}}\label{module-Labels}% +\section{Module \ocamlinlinecode{Labels}}\label{Labels}% \subsection{Attached to unit\label{L1}}% \subsection{Attached to nothing\label{L2}}% -\label{module-Labels-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Labels-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module\label{L3}}% +\label{Labels-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Labels-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module\label{L3}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Labels-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Attached to type\end{ocamlindent}% +\label{Labels-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Attached to type\end{ocamlindent}% \medbreak -\label{module-Labels-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[module-Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to value\end{ocamlindent}% +\label{Labels-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to value\end{ocamlindent}% \medbreak -\label{module-Labels-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : unit \ocamltag{arrow}{$\rightarrow$} \hyperref[module-Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to external\end{ocamlindent}% +\label{Labels-val-e}\ocamlcodefragment{\ocamltag{keyword}{val} e : unit \ocamltag{arrow}{$\rightarrow$} \hyperref[Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to external\end{ocamlindent}% \medbreak -\label{module-Labels-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Labels-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module type\label{L6}}% +\label{Labels-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Labels-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module type\label{L6}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Labels-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Labels-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L8}}% +\label{Labels-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Labels-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L8}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Labels-exception-E}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{E}}\begin{ocamlindent}Attached to exception\end{ocamlindent}% +\label{Labels-exception-E}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{E}}\begin{ocamlindent}Attached to exception\end{ocamlindent}% \medbreak -\label{module-Labels-type-x}\ocamlcodefragment{\ocamltag{keyword}{type} x = .\allowbreak{}.\allowbreak{}}\\ -\label{module-Labels-extension-decl-X}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Labels-type-x]{\ocamlinlinecode{x}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{X}}\label{module-Labels-extension-X}\\ +\label{Labels-type-x}\ocamlcodefragment{\ocamltag{keyword}{type} x = .\allowbreak{}.\allowbreak{}}\\ +\label{Labels-extension-decl-X}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Labels-type-x]{\ocamlinlinecode{x}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{X}}\label{Labels-extension-X}\\ \end{ocamltabular}% \\ \begin{ocamlindent}Attached to extension\end{ocamlindent}% \medbreak -\label{module-Labels-module-S}\ocamlcodefragment{\ocamltag{keyword}{module} S := \hyperref[module-Labels-module-A]{\ocamlinlinecode{A}}}\begin{ocamlindent}Attached to module subst\end{ocamlindent}% +\label{Labels-module-S}\ocamlcodefragment{\ocamltag{keyword}{module} S := \hyperref[Labels-A]{\ocamlinlinecode{A}}}\begin{ocamlindent}Attached to module subst\end{ocamlindent}% \medbreak -\label{module-Labels-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s := \hyperref[module-Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to type subst\end{ocamlindent}% +\label{Labels-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s := \hyperref[Labels-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}Attached to type subst\end{ocamlindent}% \medbreak -\label{module-Labels-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A'}}\label{module-Labels-type-u.A'}& Attached to constructor\\ +\label{Labels-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A'}}\label{Labels-type-u.A'}& Attached to constructor\\ \end{ocamltabular}% \\ -\label{module-Labels-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \{}\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{f : \hyperref[module-Labels-type-t]{\ocamlinlinecode{t}};\allowbreak{}}\label{module-Labels-type-v.f}& Attached to field\\ +\label{Labels-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \{}\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{f : \hyperref[Labels-type-t]{\ocamlinlinecode{t}};\allowbreak{}}\label{Labels-type-v.f}& Attached to field\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\\ Testing that labels can be referenced -\begin{itemize}\item{\hyperref[module-Labels-L1]{\ocamlinlinecode{Attached to unit}[p\pageref*{module-Labels-L1}]}}% -\item{\hyperref[module-Labels-L2]{\ocamlinlinecode{Attached to nothing}[p\pageref*{module-Labels-L2}]}}% -\item{\hyperref[module-Labels-L3]{\ocamlinlinecode{Attached to module}[p\pageref*{module-Labels-L3}]}}% -\item{\hyperref[module-Labels-L4]{\ocamlinlinecode{Attached to type}[p\pageref*{module-Labels-L4}]}}% -\item{\hyperref[module-Labels-L5]{\ocamlinlinecode{Attached to value}[p\pageref*{module-Labels-L5}]}}% -\item{\hyperref[module-Labels-L6]{\ocamlinlinecode{Attached to module type}[p\pageref*{module-Labels-L6}]}}% -\item{\hyperref[module-Labels-L7]{\ocamlinlinecode{Attached to class}[p\pageref*{module-Labels-L7}]}}% -\item{\hyperref[module-Labels-L8]{\ocamlinlinecode{Attached to class type}[p\pageref*{module-Labels-L8}]}}% -\item{\hyperref[module-Labels-L9]{\ocamlinlinecode{Attached to exception}[p\pageref*{module-Labels-L9}]}}% -\item{\hyperref[module-Labels-L10]{\ocamlinlinecode{Attached to extension}[p\pageref*{module-Labels-L10}]}}% -\item{\hyperref[module-Labels-L11]{\ocamlinlinecode{Attached to module subst}[p\pageref*{module-Labels-L11}]}}% -\item{\hyperref[module-Labels-L12]{\ocamlinlinecode{Attached to type subst}[p\pageref*{module-Labels-L12}]}}% -\item{\hyperref[module-Labels-L13]{\ocamlinlinecode{Attached to constructor}[p\pageref*{module-Labels-L13}]}}% -\item{\hyperref[module-Labels-L14]{\ocamlinlinecode{Attached to field}[p\pageref*{module-Labels-L14}]}}\end{itemize}% +\begin{itemize}\item{\hyperref[Labels-L1]{\ocamlinlinecode{Attached to unit}[p\pageref*{Labels-L1}]}}% +\item{\hyperref[Labels-L2]{\ocamlinlinecode{Attached to nothing}[p\pageref*{Labels-L2}]}}% +\item{\hyperref[Labels-L3]{\ocamlinlinecode{Attached to module}[p\pageref*{Labels-L3}]}}% +\item{\hyperref[Labels-L4]{\ocamlinlinecode{Attached to type}[p\pageref*{Labels-L4}]}}% +\item{\hyperref[Labels-L5]{\ocamlinlinecode{Attached to value}[p\pageref*{Labels-L5}]}}% +\item{\hyperref[Labels-L6]{\ocamlinlinecode{Attached to module type}[p\pageref*{Labels-L6}]}}% +\item{\hyperref[Labels-L7]{\ocamlinlinecode{Attached to class}[p\pageref*{Labels-L7}]}}% +\item{\hyperref[Labels-L8]{\ocamlinlinecode{Attached to class type}[p\pageref*{Labels-L8}]}}% +\item{\hyperref[Labels-L9]{\ocamlinlinecode{Attached to exception}[p\pageref*{Labels-L9}]}}% +\item{\hyperref[Labels-L10]{\ocamlinlinecode{Attached to extension}[p\pageref*{Labels-L10}]}}% +\item{\hyperref[Labels-L11]{\ocamlinlinecode{Attached to module subst}[p\pageref*{Labels-L11}]}}% +\item{\hyperref[Labels-L12]{\ocamlinlinecode{Attached to type subst}[p\pageref*{Labels-L12}]}}% +\item{\hyperref[Labels-L13]{\ocamlinlinecode{Attached to constructor}[p\pageref*{Labels-L13}]}}% +\item{\hyperref[Labels-L14]{\ocamlinlinecode{Attached to field}[p\pageref*{Labels-L14}]}}\end{itemize}% \input{Labels.c.tex} diff --git a/test/generators/latex/Markup.tex b/test/generators/latex/Markup.tex index 86767faf45..a97e7b1604 100644 --- a/test/generators/latex/Markup.tex +++ b/test/generators/latex/Markup.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Markup}}\label{module-Markup}% +\section{Module \ocamlinlinecode{Markup}}\label{Markup}% Here, we test the rendering of comment markup. \subsection{Sections\label{sections}}% @@ -13,7 +13,7 @@ \subsubsection{Sub-subsection headings\label{sub-subsection-headings}}% but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. \subsubsection{Anchors\label{anchors}}% -Sections can have attached \hyperref[module-Markup-anchors]{\ocamlinlinecode{Anchors}[p\pageref*{module-Markup-anchors}]}, and it is possible to \hyperref[module-Markup-anchors]{\ocamlinlinecode{link}[p\pageref*{module-Markup-anchors}]} to them. Links to section headers should not be set in source code style. +Sections can have attached \hyperref[Markup-anchors]{\ocamlinlinecode{Anchors}[p\pageref*{Markup-anchors}]}, and it is possible to \hyperref[Markup-anchors]{\ocamlinlinecode{link}[p\pageref*{Markup-anchors}]} to them. Links to section headers should not be set in source code style. \subsubsection{Paragraph\label{paragraph}}% Individual paragraphs can have a heading. @@ -41,7 +41,7 @@ \subsection{Styling\label{styling}}% \subsection{Links and references\label{links-and-references}}% This is a \href{\#}{link}\footnote{\url{\#}}. It sends you to the top of this page. Links can have markup inside them: \href{\#}{\bold{bold}}\footnote{\url{\#}}, \href{\#}{\emph{italics}}\footnote{\url{\#}}, \href{\#}{\emph{emphasis}}\footnote{\url{\#}}, \href{\#}{super\textsuperscript{script}}\footnote{\url{\#}}, \href{\#}{sub\textsubscript{script}}\footnote{\url{\#}}, and \href{\#}{\ocamlinlinecode{code}}\footnote{\url{\#}}. Links can also be nested \emph{\href{\#}{inside}\footnote{\url{\#}}} markup. Links cannot be nested inside each other. This link has no replacement text: \href{\#}{\#}\footnote{\url{\#}}. The text is filled in by odoc. This is a shorthand link: \href{\#}{\#}\footnote{\url{\#}}. The text is also filled in by odoc in this case. -This is a reference to \hyperref[module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Markup-val-foo}]}. References can have replacement text: \hyperref[module-Markup-val-foo]{\ocamlinlinecode{the value foo}[p\pageref*{module-Markup-val-foo}]}. Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: \hyperref[module-Markup-val-foo]{\ocamlinlinecode{\bold{bold}}[p\pageref*{module-Markup-val-foo}]}, \hyperref[module-Markup-val-foo]{\ocamlinlinecode{\emph{italic}}[p\pageref*{module-Markup-val-foo}]}, \hyperref[module-Markup-val-foo]{\ocamlinlinecode{\emph{emphasis}}[p\pageref*{module-Markup-val-foo}]}, \hyperref[module-Markup-val-foo]{\ocamlinlinecode{super\textsuperscript{script}}[p\pageref*{module-Markup-val-foo}]}, \hyperref[module-Markup-val-foo]{\ocamlinlinecode{sub\textsubscript{script}}[p\pageref*{module-Markup-val-foo}]}, and \hyperref[module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{code}}[p\pageref*{module-Markup-val-foo}]}. It's also possible to surround a reference in a style: \bold{\hyperref[module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Markup-val-foo}]}}. References can't be nested inside references, and links and references can't be nested inside each other. +This is a reference to \hyperref[Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Markup-val-foo}]}. References can have replacement text: \hyperref[Markup-val-foo]{\ocamlinlinecode{the value foo}[p\pageref*{Markup-val-foo}]}. Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: \hyperref[Markup-val-foo]{\ocamlinlinecode{\bold{bold}}[p\pageref*{Markup-val-foo}]}, \hyperref[Markup-val-foo]{\ocamlinlinecode{\emph{italic}}[p\pageref*{Markup-val-foo}]}, \hyperref[Markup-val-foo]{\ocamlinlinecode{\emph{emphasis}}[p\pageref*{Markup-val-foo}]}, \hyperref[Markup-val-foo]{\ocamlinlinecode{super\textsuperscript{script}}[p\pageref*{Markup-val-foo}]}, \hyperref[Markup-val-foo]{\ocamlinlinecode{sub\textsubscript{script}}[p\pageref*{Markup-val-foo}]}, and \hyperref[Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{code}}[p\pageref*{Markup-val-foo}]}. It's also possible to surround a reference in a style: \bold{\hyperref[Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Markup-val-foo}]}}. References can't be nested inside references, and links and references can't be nested inside each other. \subsection{Preformatted text\label{preformatted-text}}% This is a code block:\medbreak @@ -78,7 +78,7 @@ \subsection{Lists\label{lists}}% \begin{itemize}\item{\begin{itemize}\item{lists}% \item{can be nested}% \item{and can include references}% -\item{\hyperref[module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Markup-val-foo}]}}\end{itemize}% +\item{\hyperref[Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Markup-val-foo}]}}\end{itemize}% }\end{itemize}% \subsection{Unicode\label{unicode}}% The parser supports any ASCII-compatible encoding, in particuλar UTF-8. @@ -100,11 +100,11 @@ \subsection{Math\label{math}}% \subsection{Modules\label{modules}}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{\hyperref[module-Markup-module-X]{\ocamlinlinecode{\ocamlinlinecode{X}}[p\pageref*{module-Markup-module-X}]}}]{}\end{description}% +\item[{\hyperref[Markup-X]{\ocamlinlinecode{\ocamlinlinecode{X}}[p\pageref*{Markup-X}]}}]{}\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{\hyperref[module-Markup-module-X]{\ocamlinlinecode{\ocamlinlinecode{X}}[p\pageref*{module-Markup-module-X}]}}]{}% -\item[{\hyperref[module-Markup-module-Y]{\ocamlinlinecode{\ocamlinlinecode{Y}}[p\pageref*{module-Markup-module-Y}]}}]{}\end{description}% +\item[{\hyperref[Markup-X]{\ocamlinlinecode{\ocamlinlinecode{X}}[p\pageref*{Markup-X}]}}]{}% +\item[{\hyperref[Markup-Y]{\ocamlinlinecode{\ocamlinlinecode{Y}}[p\pageref*{Markup-Y}]}}]{}\end{description}% \subsection{Tables\label{tables}}\\ \begin{ocamltabular}{w{l}{0.250\textwidth}w{c}{0.250\textwidth}w{r}{0.250\textwidth}p{0.250\textwidth}}\bold{Left @@ -247,13 +247,13 @@ \subsection{Tags\label{tags}}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{version}]{-1}\end{description}% -\label{module-Markup-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Comments in structure items \bold{support} \emph{markup}, t\textsuperscript{o}\textsubscript{o}.\end{ocamlindent}% +\label{Markup-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Comments in structure items \bold{support} \emph{markup}, t\textsuperscript{o}\textsubscript{o}.\end{ocamlindent}% \medbreak Some modules to support references. -\label{module-Markup-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Markup-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Markup-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Markup-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Markup-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Markup-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Markup-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Markup-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/generators/latex/Module.tex b/test/generators/latex/Module.tex index 8cbc872e37..f1a387ae37 100644 --- a/test/generators/latex/Module.tex +++ b/test/generators/latex/Module.tex @@ -1,68 +1,68 @@ -\section{Module \ocamlinlinecode{Module}}\label{module-Module}% +\section{Module \ocamlinlinecode{Module}}\label{Module}% Foo. -\label{module-Module-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See \href{https://caml.inria.fr/mantis/view.php?id=7701}{https://caml.inria.fr/mantis/view.php?id=7701}\footnote{\url{https://caml.inria.fr/mantis/view.php?id=7701}}.\end{ocamlindent}% +\label{Module-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See \href{https://caml.inria.fr/mantis/view.php?id=7701}{https://caml.inria.fr/mantis/view.php?id=7701}\footnote{\url{https://caml.inria.fr/mantis/view.php?id=7701}}.\end{ocamlindent}% \medbreak -\label{module-Module-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Module-module-type-S-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Module-module-type-S-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ -\label{module-Module-module-type-S-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ -\label{module-Module-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-type-S-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module-module-type-S-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module-module-type-S-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{Module-module-type-S-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{Module-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-module-type-S-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S1}\\ -\label{module-Module-module-type-S2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S2 = \hyperref[module-Module-module-type-S]{\ocamlinlinecode{S}}}\\ -\label{module-Module-module-type-S3}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S3]{\ocamlinlinecode{S3}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ -\label{module-Module-module-type-S3-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = string}\\ -\label{module-Module-module-type-S3-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ -\label{module-Module-module-type-S3-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ -\label{module-Module-module-type-S3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-type-S3-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S1}\\ +\label{Module-module-type-S2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S2 = \hyperref[Module-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Module-module-type-S3}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S3]{\ocamlinlinecode{S3}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ +\label{Module-module-type-S3-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = string}\\ +\label{Module-module-type-S3-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{Module-module-type-S3-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{Module-module-type-S3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-module-type-S3-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-type-S4}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S4]{\ocamlinlinecode{S4}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S4-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Module-module-type-S4-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ -\label{module-Module-module-type-S4-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ -\label{module-Module-module-type-S4-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-type-S4-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-type-S4}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S4]{\ocamlinlinecode{S4}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S4-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module-module-type-S4-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{Module-module-type-S4-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{Module-module-type-S4-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-module-type-S4-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-type-S5}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S5]{\ocamlinlinecode{S5}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Module-module-type-S5-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Module-module-type-S5-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ -\label{module-Module-module-type-S5-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-type-S5-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-type-S5}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S5]{\ocamlinlinecode{S5}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module-module-type-S5-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module-module-type-S5-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{Module-module-type-S5-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-module-type-S5-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-type-result}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) result}\\ -\label{module-Module-module-type-S6}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S6]{\ocamlinlinecode{S6}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S6-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Module-module-type-S6-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Module-module-type-S6-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ -\label{module-Module-module-type-S6-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-type-S6-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-type-result}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) result}\\ +\label{Module-module-type-S6}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S6]{\ocamlinlinecode{S6}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S6-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module-module-type-S6-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module-module-type-S6-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{Module-module-type-S6-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-module-type-S6-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-type-S7}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S7]{\ocamlinlinecode{S7}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S7-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Module-module-type-S7-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Module-module-type-S7-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ -\label{module-Module-module-type-S7-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ -\label{module-Module-module-type-S7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[module-Module-module-M']{\ocamlinlinecode{M'}}}\\ +\label{Module-module-type-S7}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S7]{\ocamlinlinecode{S7}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S7-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module-module-type-S7-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module-module-type-S7-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{Module-module-type-S7-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{Module-module-type-S7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[Module-M']{\ocamlinlinecode{M'}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-type-S8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S8]{\ocamlinlinecode{S8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module-module-type-S8-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Module-module-type-S8-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Module-module-type-S8-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ -\label{module-Module-module-type-S8-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{Module-module-type-S8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S8]{\ocamlinlinecode{S8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module-module-type-S8-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module-module-type-S8-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module-module-type-S8-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{Module-module-type-S8-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-type-S9}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module-module-type-S9]{\ocamlinlinecode{S9}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-type-S9}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module-module-type-S9]{\ocamlinlinecode{S9}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-Mutually}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-Mutually]{\ocamlinlinecode{Mutually}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-Mutually}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-Mutually]{\ocamlinlinecode{Mutually}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module-module-Recursive}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module-module-Recursive]{\ocamlinlinecode{Recursive}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module-module-Recursive}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module-Recursive]{\ocamlinlinecode{Recursive}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/generators/latex/Module_type_alias.tex b/test/generators/latex/Module_type_alias.tex index e5b920e653..ad4f6c6556 100644 --- a/test/generators/latex/Module_type_alias.tex +++ b/test/generators/latex/Module_type_alias.tex @@ -1,37 +1,37 @@ -\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}alias}}\label{module-Module_type_alias}% +\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}alias}}\label{Module_type_alias}% Module Type Aliases -\label{module-Module_type_alias-module-type-A}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_alias-module-type-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_alias-module-type-A-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\ +\label{Module_type_alias-module-type-A}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_alias-module-type-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_alias-module-type-A-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_alias-module-type-B}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_alias-module-type-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{module-Module_type_alias-module-type-B-argument-1-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_alias-module-type-B-argument-1-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_alias-module-type-B-argument-1-C-type-c}\ocamlcodefragment{\ocamltag{keyword}{type} c}\\ +\label{Module_type_alias-module-type-B}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_alias-module-type-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{Module_type_alias-module-type-B-argument-1-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_alias-module-type-B-argument-1-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_alias-module-type-B-argument-1-C-type-c}\ocamlcodefragment{\ocamltag{keyword}{type} c}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% -\label{module-Module_type_alias-module-type-B-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ +\label{Module_type_alias-module-type-B-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_alias-module-type-D}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} D = \hyperref[module-Module_type_alias-module-type-A]{\ocamlinlinecode{A}}}\\ -\label{module-Module_type_alias-module-type-E}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_alias-module-type-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters_2}}% -\label{module-Module_type_alias-module-type-E-argument-1-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_alias-module-type-E-argument-1-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_alias-module-type-E-argument-1-F-type-f}\ocamlcodefragment{\ocamltag{keyword}{type} f}\\ +\label{Module_type_alias-module-type-D}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} D = \hyperref[Module_type_alias-module-type-A]{\ocamlinlinecode{A}}}\\ +\label{Module_type_alias-module-type-E}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_alias-module-type-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters_2}}% +\label{Module_type_alias-module-type-E-argument-1-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_alias-module-type-E-argument-1-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_alias-module-type-E-argument-1-F-type-f}\ocamlcodefragment{\ocamltag{keyword}{type} f}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_alias-module-type-E-argument-2-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_alias-module-type-E-argument-2-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_alias-module-type-E-argument-2-C-type-c}\ocamlcodefragment{\ocamltag{keyword}{type} c}\\ +\label{Module_type_alias-module-type-E-argument-2-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_alias-module-type-E-argument-2-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_alias-module-type-E-argument-2-C-type-c}\ocamlcodefragment{\ocamltag{keyword}{type} c}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature_2}}% -\label{module-Module_type_alias-module-type-E-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ +\label{Module_type_alias-module-type-E-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_alias-module-type-G}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_alias-module-type-G]{\ocamlinlinecode{G}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters_3}}% -\label{module-Module_type_alias-module-type-G-argument-1-H}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_alias-module-type-G-argument-1-H]{\ocamlinlinecode{H}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_alias-module-type-G-argument-1-H-type-h}\ocamlcodefragment{\ocamltag{keyword}{type} h}\\ +\label{Module_type_alias-module-type-G}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_alias-module-type-G]{\ocamlinlinecode{G}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters_3}}% +\label{Module_type_alias-module-type-G-argument-1-H}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_alias-module-type-G-argument-1-H]{\ocamlinlinecode{H}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_alias-module-type-G-argument-1-H-type-h}\ocamlcodefragment{\ocamltag{keyword}{type} h}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature_3}}% -\label{module-Module_type_alias-module-type-G-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\ +\label{Module_type_alias-module-type-G-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_alias-module-type-I}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} I = \hyperref[module-Module_type_alias-module-type-B]{\ocamlinlinecode{B}}}\\ +\label{Module_type_alias-module-type-I}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} I = \hyperref[Module_type_alias-module-type-B]{\ocamlinlinecode{B}}}\\ diff --git a/test/generators/latex/Module_type_of.T.N.tex b/test/generators/latex/Module_type_of.T.N.tex index 11b3fbcf97..18103111f5 100644 --- a/test/generators/latex/Module_type_of.T.N.tex +++ b/test/generators/latex/Module_type_of.T.N.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{T.\allowbreak{}N}}\label{module-Module_type_of-module-T-module-N}% -\label{module-Module_type_of-module-T-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Module_type_of-module-X-type-t]{\ocamlinlinecode{M.\allowbreak{}t}}}\\ +\section{Module \ocamlinlinecode{T.\allowbreak{}N}}\label{Module_type_of-T-N}% +\label{Module_type_of-T-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Module_type_of-X-type-t]{\ocamlinlinecode{M.\allowbreak{}t}}}\\ diff --git a/test/generators/latex/Module_type_of.T.tex b/test/generators/latex/Module_type_of.T.tex index f4e38fb64b..c47283fdc5 100644 --- a/test/generators/latex/Module_type_of.T.tex +++ b/test/generators/latex/Module_type_of.T.tex @@ -1,8 +1,8 @@ -\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}of.\allowbreak{}T}}\label{module-Module_type_of-module-T}% -\label{module-Module_type_of-module-T-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_of-module-T-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_of-module-T-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}of.\allowbreak{}T}}\label{Module_type_of-T}% +\label{Module_type_of-T-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_of-T-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_of-T-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_of-module-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[module-Module_type_of-module-X]{\ocamlinlinecode{X}}}\\ -\label{module-Module_type_of-module-T-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_of-module-T-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[module-Module_type_of-module-X]{\ocamlinlinecode{M}} \ocamltag{keyword}{end}}\\ +\label{Module_type_of-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[Module_type_of-X]{\ocamlinlinecode{X}}}\\ +\label{Module_type_of-T-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_of-T-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \ocamltag{keyword}{struct} \ocamltag{keyword}{include} \hyperref[Module_type_of-X]{\ocamlinlinecode{M}} \ocamltag{keyword}{end}}\\ \input{Module_type_of.T.N.tex} diff --git a/test/generators/latex/Module_type_of.tex b/test/generators/latex/Module_type_of.tex index 91cec6069d..1ceac4b393 100644 --- a/test/generators/latex/Module_type_of.tex +++ b/test/generators/latex/Module_type_of.tex @@ -1,19 +1,19 @@ -\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}of}}\label{module-Module_type_of}% -\label{module-Module_type_of-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_of-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_of-module-type-S-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_of-module-type-S-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_of-module-type-S-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}of}}\label{Module_type_of}% +\label{Module_type_of-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_of-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_of-module-type-S-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_of-module-type-S-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_of-module-type-S-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_of-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_of-module-type-S-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_of-module-type-S-module-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module_type_of-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_of-module-type-S-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_of-module-type-S-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_of-module-type-S-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_of-module-type-S-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_of-module-type-S-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Module_type_of-module-type-S-module-M-type-t]{\ocamlinlinecode{M.\allowbreak{}t}}}\\ +\label{Module_type_of-module-type-S-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_of-module-type-S-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_of-module-type-S-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Module_type_of-module-type-S-M-type-t]{\ocamlinlinecode{M.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_of-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_of-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_of-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Module_type_of-module-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Module_type_of-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_of-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_of-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Module_type_of-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_of-module-T}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_of-module-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ : \hyperref[module-Module_type_of-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[module-Module_type_of-module-type-S-module-M]{\ocamlinlinecode{M}} = \hyperref[module-Module_type_of-module-X]{\ocamlinlinecode{X}}}\\ +\label{Module_type_of-module-T}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_of-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ : \hyperref[Module_type_of-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[Module_type_of-module-type-S-M]{\ocamlinlinecode{M}} = \hyperref[Module_type_of-X]{\ocamlinlinecode{X}}}\\ \input{Module_type_of.T.tex} diff --git a/test/generators/latex/Module_type_subst.tex b/test/generators/latex/Module_type_subst.tex index ca0159c281..1d83782404 100644 --- a/test/generators/latex/Module_type_subst.tex +++ b/test/generators/latex/Module_type_subst.tex @@ -1,64 +1,64 @@ -\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}subst}}\label{module-Module_type_subst}% -\label{module-Module_type_subst-module-Local}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Local]{\ocamlinlinecode{Local}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Local-type-local}\ocamlcodefragment{\ocamltag{keyword}{type} local := int * int}\\ -\label{module-Module_type_subst-module-Local-module-type-local}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Local-module-type-local]{\ocamlinlinecode{local}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Local-module-type-local-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Module_type_subst-module-Local-type-local]{\ocamlinlinecode{local}}}\\ +\section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}subst}}\label{Module_type_subst}% +\label{Module_type_subst-module-Local}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Local]{\ocamlinlinecode{Local}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Local-type-local}\ocamlcodefragment{\ocamltag{keyword}{type} local := int * int}\\ +\label{Module_type_subst-Local-module-type-local}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Local-module-type-local]{\ocamlinlinecode{local}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Local-module-type-local-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Module_type_subst-Local-type-local]{\ocamlinlinecode{local}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Local-module-type-w}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} w = \hyperref[module-Module_type_subst-module-Local-module-type-local]{\ocamlinlinecode{local}}}\\ -\label{module-Module_type_subst-module-Local-module-type-s}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Local-module-type-s]{\ocamlinlinecode{s}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Local-module-type-w}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} w = \hyperref[Module_type_subst-Local-module-type-local]{\ocamlinlinecode{local}}}\\ +\label{Module_type_subst-Local-module-type-s}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Local-module-type-s]{\ocamlinlinecode{s}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-type-s}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-module-type-s}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Basic]{\ocamlinlinecode{Basic}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-u}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-u]{\ocamlinlinecode{u}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-u-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-u-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-module-Basic}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Basic]{\ocamlinlinecode{Basic}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-u}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-u]{\ocamlinlinecode{u}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-u-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-u-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-with_}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-with_]{\ocamlinlinecode{with\_\allowbreak{}}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-with_-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[module-Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\\ +\label{Module_type_subst-Basic-module-type-with_}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-with_]{\ocamlinlinecode{with\_\allowbreak{}}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-with_-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-u2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-u2]{\ocamlinlinecode{u2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-u2-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-u2-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Basic-module-type-u2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-u2]{\ocamlinlinecode{u2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-u2-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-u2-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-u2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Basic-module-type-u2-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Basic-module-type-u2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Basic-module-type-u2-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-with_2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-with_2]{\ocamlinlinecode{with\_\allowbreak{}2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-with_2-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-with_2-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Basic-module-type-with_2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-with_2]{\ocamlinlinecode{with\_\allowbreak{}2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-with_2-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-with_2-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-with_2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Basic-module-type-with_2-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Basic-module-type-with_2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Basic-module-type-with_2-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-a}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-a]{\ocamlinlinecode{a}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-a-module-type-b}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} b = \hyperref[module-Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\\ -\label{module-Module_type_subst-module-Basic-module-type-a-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Basic-module-type-a-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Basic-module-type-a}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-a]{\ocamlinlinecode{a}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-a-module-type-b}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} b = \hyperref[Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\\ +\label{Module_type_subst-Basic-module-type-a-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Basic-module-type-a-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Basic-module-type-c}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Basic-module-type-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Basic-module-type-c-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Basic-module-type-c-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Basic-module-type-c}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Basic-module-type-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Basic-module-type-c-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Basic-module-type-c-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Nested}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Nested]{\ocamlinlinecode{Nested}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Nested-module-type-nested}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Nested-module-type-nested]{\ocamlinlinecode{nested}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Nested-module-type-nested-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Nested-module-type-nested-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Nested-module-type-nested-module-N-module-type-t}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Nested-module-type-nested-module-N-module-type-t]{\ocamlinlinecode{t}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-module-Nested}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Nested]{\ocamlinlinecode{Nested}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Nested-module-type-nested}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Nested-module-type-nested]{\ocamlinlinecode{nested}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Nested-module-type-nested-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Nested-module-type-nested-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Nested-module-type-nested-N-module-type-t}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Nested-module-type-nested-N-module-type-t]{\ocamlinlinecode{t}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Nested-module-type-with_}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Nested-module-type-with_]{\ocamlinlinecode{with\_\allowbreak{}}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Nested-module-type-with_-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Nested-module-type-with_-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Nested-module-type-with_-module-N-module-type-t}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} t = \hyperref[module-Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\\ +\label{Module_type_subst-Nested-module-type-with_}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Nested-module-type-with_]{\ocamlinlinecode{with\_\allowbreak{}}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Nested-module-type-with_-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Nested-module-type-with_-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Nested-module-type-with_-N-module-type-t}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} t = \hyperref[Module_type_subst-module-type-s]{\ocamlinlinecode{s}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Nested-module-type-with_subst}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Nested-module-type-with_subst]{\ocamlinlinecode{with\_\allowbreak{}subst}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Nested-module-type-with_subst-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Nested-module-type-with_subst-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Module_type_subst-Nested-module-type-with_subst}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Nested-module-type-with_subst]{\ocamlinlinecode{with\_\allowbreak{}subst}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Nested-module-type-with_subst-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Nested-module-type-with_subst-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Structural}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Module_type_subst-module-Structural]{\ocamlinlinecode{Structural}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-u}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-u]{\ocamlinlinecode{u}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-u-module-type-a}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-u-module-type-a]{\ocamlinlinecode{a}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b]{\ocamlinlinecode{b}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b-module-type-c}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b-module-type-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b-module-type-c-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b-module-type-c-type-t]{\ocamlinlinecode{t}}}\label{module-Module_type_subst-module-Structural-module-type-u-module-type-a-module-type-b-module-type-c-type-t.A}\\ +\label{Module_type_subst-module-Structural}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Module_type_subst-Structural]{\ocamlinlinecode{Structural}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-u}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-u]{\ocamlinlinecode{u}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-u-module-type-a}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-u-module-type-a]{\ocamlinlinecode{a}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-u-module-type-a-module-type-b}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-u-module-type-a-module-type-b]{\ocamlinlinecode{b}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c-type-t]{\ocamlinlinecode{t}}}\label{Module_type_subst-Structural-module-type-u-module-type-a-module-type-b-module-type-c-type-t.A}\\ \end{ocamltabular}% \\ \end{ocamlindent}% @@ -69,8 +69,8 @@ \section{Module \ocamlinlinecode{Module\_\allowbreak{}type\_\allowbreak{}subst}} \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Module_type_subst-module-Structural-module-type-w}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-w]{\ocamlinlinecode{w}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-w-module-type-a}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-w-module-type-a]{\ocamlinlinecode{a}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b]{\ocamlinlinecode{b}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b-module-type-c}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b-module-type-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b-module-type-c-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b-module-type-c-type-t]{\ocamlinlinecode{t}}}\label{module-Module_type_subst-module-Structural-module-type-w-module-type-a-module-type-b-module-type-c-type-t.A}\\ +\label{Module_type_subst-Structural-module-type-w}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-w]{\ocamlinlinecode{w}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-w-module-type-a}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-w-module-type-a]{\ocamlinlinecode{a}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-w-module-type-a-module-type-b}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-w-module-type-a-module-type-b]{\ocamlinlinecode{b}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c-type-t]{\ocamlinlinecode{t}}}\label{Module_type_subst-Structural-module-type-w-module-type-a-module-type-b-module-type-c-type-t.A}\\ \end{ocamltabular}% \\ \end{ocamlindent}% diff --git a/test/generators/latex/Nested.F.tex b/test/generators/latex/Nested.F.tex index c2bdcf7ea5..f1058a16de 100644 --- a/test/generators/latex/Nested.F.tex +++ b/test/generators/latex/Nested.F.tex @@ -1,25 +1,25 @@ -\section{Module \ocamlinlinecode{Nested.\allowbreak{}F}}\label{module-Nested-module-F}% +\section{Module \ocamlinlinecode{Nested.\allowbreak{}F}}\label{Nested-F}% This is a functor F. Some additional comments. \subsection{Parameters\label{parameters}}% -\label{module-Nested-module-F-argument-1-Arg1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% -\label{module-Nested-module-F-argument-1-Arg1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{Nested-F-argument-1-Arg1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Nested-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% +\label{Nested-F-argument-1-Arg1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \subsubsection{Values\label{values}}% -\label{module-Nested-module-F-argument-1-Arg1-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% +\label{Nested-F-argument-1-Arg1-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[Nested-F-argument-1-Arg1-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Nested-module-F-argument-2-Arg2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type_2}}% -\label{module-Nested-module-F-argument-2-Arg2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{Nested-F-argument-2-Arg2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Nested-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type_2}}% +\label{Nested-F-argument-2-Arg2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% \subsection{Type\label{type_3}}% -\label{module-Nested-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{Arg1.\allowbreak{}t}} * \hyperref[module-Nested-module-F-argument-2-Arg2-type-t]{\ocamlinlinecode{Arg2.\allowbreak{}t}}}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{Nested-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Nested-F-argument-1-Arg1-type-t]{\ocamlinlinecode{Arg1.\allowbreak{}t}} * \hyperref[Nested-F-argument-2-Arg2-type-t]{\ocamlinlinecode{Arg2.\allowbreak{}t}}}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Nested.inherits.tex b/test/generators/latex/Nested.inherits.tex index 626aa7ad47..7e0fa5d89a 100644 --- a/test/generators/latex/Nested.inherits.tex +++ b/test/generators/latex/Nested.inherits.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Nested.\allowbreak{}inherits}}\label{module-Nested-class-inherits}% -\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[module-Nested-class-z]{\ocamlinlinecode{z}}}\\ +\section{Class \ocamlinlinecode{Nested.\allowbreak{}inherits}}\label{Nested-class-inherits}% +\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[Nested-class-z]{\ocamlinlinecode{z}}}\\ diff --git a/test/generators/latex/Nested.tex b/test/generators/latex/Nested.tex index d62a5a2039..7ff4ffbf86 100644 --- a/test/generators/latex/Nested.tex +++ b/test/generators/latex/Nested.tex @@ -1,33 +1,33 @@ -\section{Module \ocamlinlinecode{Nested}}\label{module-Nested}% +\section{Module \ocamlinlinecode{Nested}}\label{Nested}% This comment needs to be here before \#235 is fixed. \subsection{Module\label{module}}% -\label{module-Nested-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Nested-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% -\label{module-Nested-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{Nested-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Nested-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% +\label{Nested-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \subsubsection{Values\label{values}}% -\label{module-Nested-module-X-val-x}\ocamlcodefragment{\ocamltag{keyword}{val} x : \hyperref[module-Nested-module-X-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of x.\end{ocamlindent}% +\label{Nested-X-val-x}\ocamlcodefragment{\ocamltag{keyword}{val} x : \hyperref[Nested-X-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of x.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module X.\end{ocamlindent}% \medbreak \subsection{Module type\label{module-type}}% -\label{module-Nested-module-type-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Nested-module-type-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type_2}}% -\label{module-Nested-module-type-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{Nested-module-type-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Nested-module-type-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type_2}}% +\label{Nested-module-type-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \subsubsection{Values\label{values_2}}% -\label{module-Nested-module-type-Y-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[module-Nested-module-type-Y-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% +\label{Nested-module-type-Y-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[Nested-module-type-Y-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module type Y.\end{ocamlindent}% \medbreak \subsection{Functor\label{functor}}% -\label{module-Nested-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Nested-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ (\hyperref[module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}} : \hyperref[module-Nested-module-type-Y]{\ocamlinlinecode{Y}}) (\hyperref[module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is a functor F.\end{ocamlindent}% +\label{Nested-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Nested-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ (\hyperref[Nested-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}} : \hyperref[Nested-module-type-Y]{\ocamlinlinecode{Y}}) (\hyperref[Nested-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is a functor F.\end{ocamlindent}% \medbreak \subsection{Class\label{class}}% -\label{module-Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}% +\label{Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}% \medbreak -\label{module-Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Nested.F.tex} \input{Nested.z.tex} diff --git a/test/generators/latex/Nested.z.tex b/test/generators/latex/Nested.z.tex index bae6c92f1a..37cace571f 100644 --- a/test/generators/latex/Nested.z.tex +++ b/test/generators/latex/Nested.z.tex @@ -1,14 +1,14 @@ -\section{Class \ocamlinlinecode{Nested.\allowbreak{}z}}\label{module-Nested-class-z}% +\section{Class \ocamlinlinecode{Nested.\allowbreak{}z}}\label{Nested-class-z}% This is class z. Some additional comments. -\label{module-Nested-class-z-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : int}\begin{ocamlindent}Some value.\end{ocamlindent}% +\label{Nested-class-z-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : int}\begin{ocamlindent}Some value.\end{ocamlindent}% \medbreak -\label{module-Nested-class-z-val-y'}\ocamlcodefragment{\ocamltag{keyword}{val} \ocamltag{keyword}{mutable} \ocamltag{keyword}{virtual} y' : int}\\ +\label{Nested-class-z-val-y'}\ocamlcodefragment{\ocamltag{keyword}{val} \ocamltag{keyword}{mutable} \ocamltag{keyword}{virtual} y' : int}\\ \subsection{Methods\label{methods}}% -\label{module-Nested-class-z-method-z}\ocamlcodefragment{\ocamltag{keyword}{method} z : int}\begin{ocamlindent}Some method.\end{ocamlindent}% +\label{Nested-class-z-method-z}\ocamlcodefragment{\ocamltag{keyword}{method} z : int}\begin{ocamlindent}Some method.\end{ocamlindent}% \medbreak -\label{module-Nested-class-z-method-z'}\ocamlcodefragment{\ocamltag{keyword}{method} \ocamltag{keyword}{private} \ocamltag{keyword}{virtual} z' : int}\\ +\label{Nested-class-z-method-z'}\ocamlcodefragment{\ocamltag{keyword}{method} \ocamltag{keyword}{private} \ocamltag{keyword}{virtual} z' : int}\\ diff --git a/test/generators/latex/Ocamlary.Dep12.tex b/test/generators/latex/Ocamlary.Dep12.tex index c8e7301d08..8361527fd6 100644 --- a/test/generators/latex/Ocamlary.Dep12.tex +++ b/test/generators/latex/Ocamlary.Dep12.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep12}}\label{module-Ocamlary-module-Dep12}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep12}}\label{Ocamlary-Dep12}% \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-Dep12-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep12-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep12-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ +\label{Ocamlary-Dep12-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep12-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep12-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-Dep12-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[module-Ocamlary-module-Dep12-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\ +\label{Ocamlary-Dep12-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[Ocamlary-Dep12-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\ diff --git a/test/generators/latex/Ocamlary.Dep13.c.tex b/test/generators/latex/Ocamlary.Dep13.c.tex index 034f051f92..d9f025d7f4 100644 --- a/test/generators/latex/Ocamlary.Dep13.c.tex +++ b/test/generators/latex/Ocamlary.Dep13.c.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Dep13.\allowbreak{}c}}\label{module-Ocamlary-module-Dep13-class-c}% -\label{module-Ocamlary-module-Dep13-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ +\section{Class \ocamlinlinecode{Dep13.\allowbreak{}c}}\label{Ocamlary-Dep13-class-c}% +\label{Ocamlary-Dep13-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ diff --git a/test/generators/latex/Ocamlary.Dep13.tex b/test/generators/latex/Ocamlary.Dep13.tex index e7768b1019..8a2157db5f 100644 --- a/test/generators/latex/Ocamlary.Dep13.tex +++ b/test/generators/latex/Ocamlary.Dep13.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep13}}\label{module-Ocamlary-module-Dep13}% -\label{module-Ocamlary-module-Dep13-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep13-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep13}}\label{Ocamlary-Dep13}% +\label{Ocamlary-Dep13-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Ocamlary-Dep13-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Ocamlary.Dep13.c.tex} diff --git a/test/generators/latex/Ocamlary.Dep2.tex b/test/generators/latex/Ocamlary.Dep2.tex index 91cd92fa9d..a1d02d2301 100644 --- a/test/generators/latex/Ocamlary.Dep2.tex +++ b/test/generators/latex/Ocamlary.Dep2.tex @@ -1,15 +1,15 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep2}}\label{module-Ocamlary-module-Dep2}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep2}}\label{Ocamlary-Dep2}% \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-Dep2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep2-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ -\label{module-Ocamlary-module-Dep2-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep2-argument-1-Arg-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep2-argument-1-Arg-module-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[module-Ocamlary-module-Dep2-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-Dep2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep2-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ +\label{Ocamlary-Dep2-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep2-argument-1-Arg-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep2-argument-1-Arg-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[Ocamlary-Dep2-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-Dep2-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep2-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep2-module-A-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[module-Ocamlary-module-Dep2-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\ +\label{Ocamlary-Dep2-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep2-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep2-A-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[Ocamlary-Dep2-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep2-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[module-Ocamlary-module-Dep2-module-A-module-Y]{\ocamlinlinecode{A.\allowbreak{}Y}}}\\ +\label{Ocamlary-Dep2-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[Ocamlary-Dep2-A-module-Y]{\ocamlinlinecode{A.\allowbreak{}Y}}}\\ diff --git a/test/generators/latex/Ocamlary.Dep5.Z.tex b/test/generators/latex/Ocamlary.Dep5.Z.tex index d3cc24003b..8619cea5e2 100644 --- a/test/generators/latex/Ocamlary.Dep5.Z.tex +++ b/test/generators/latex/Ocamlary.Dep5.Z.tex @@ -1,5 +1,5 @@ -\section{Module \ocamlinlinecode{Dep5.\allowbreak{}Z}}\label{module-Ocamlary-module-Dep5-module-Z}% -\label{module-Ocamlary-module-Dep5-module-Z-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{Arg.\allowbreak{}T}}}\\ -\label{module-Ocamlary-module-Dep5-module-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y = \hyperref[module-Ocamlary-module-Dep3]{\ocamlinlinecode{Dep3}}}\\ +\section{Module \ocamlinlinecode{Dep5.\allowbreak{}Z}}\label{Ocamlary-Dep5-Z}% +\label{Ocamlary-Dep5-Z-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{Arg.\allowbreak{}T}}}\\ +\label{Ocamlary-Dep5-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y = \hyperref[Ocamlary-Dep3]{\ocamlinlinecode{Dep3}}}\\ diff --git a/test/generators/latex/Ocamlary.Dep5.tex b/test/generators/latex/Ocamlary.Dep5.tex index f48efbd907..f9e5cb567c 100644 --- a/test/generators/latex/Ocamlary.Dep5.tex +++ b/test/generators/latex/Ocamlary.Dep5.tex @@ -1,15 +1,15 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep5}}\label{module-Ocamlary-module-Dep5}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep5}}\label{Ocamlary-Dep5}% \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-Dep5-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\ -\label{module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\\ -\label{module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-Dep5-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep5-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep5-argument-1-Arg-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\ +\label{Ocamlary-Dep5-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep5-argument-1-Arg-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\\ +\label{Ocamlary-Dep5-argument-1-Arg-module-type-S-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-S-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep5-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\\ +\label{Ocamlary-Dep5-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} X : \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-Dep5-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep5-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep5-argument-1-Arg-module-type-S-module-Y]{\ocamlinlinecode{Y}} = \hyperref[module-Ocamlary-module-Dep3]{\ocamlinlinecode{Dep3}}}\\ +\label{Ocamlary-Dep5-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep5-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[Ocamlary-Dep5-argument-1-Arg-module-type-S-Y]{\ocamlinlinecode{Y}} = \hyperref[Ocamlary-Dep3]{\ocamlinlinecode{Dep3}}}\\ \input{Ocamlary.Dep5.Z.tex} diff --git a/test/generators/latex/Ocamlary.Dep7.M.tex b/test/generators/latex/Ocamlary.Dep7.M.tex index db865c89f5..70e1b3266d 100644 --- a/test/generators/latex/Ocamlary.Dep7.M.tex +++ b/test/generators/latex/Ocamlary.Dep7.M.tex @@ -1,5 +1,5 @@ -\section{Module \ocamlinlinecode{Dep7.\allowbreak{}M}}\label{module-Ocamlary-module-Dep7-module-M}% -\label{module-Ocamlary-module-Dep7-module-M-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\ -\label{module-Ocamlary-module-Dep7-module-M-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{R}}}\\ +\section{Module \ocamlinlinecode{Dep7.\allowbreak{}M}}\label{Ocamlary-Dep7-M}% +\label{Ocamlary-Dep7-M-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{Arg.\allowbreak{}S}}}\\ +\label{Ocamlary-Dep7-M-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{R}}}\\ diff --git a/test/generators/latex/Ocamlary.Dep7.tex b/test/generators/latex/Ocamlary.Dep7.tex index 19a1683bb6..aba3461509 100644 --- a/test/generators/latex/Ocamlary.Dep7.tex +++ b/test/generators/latex/Ocamlary.Dep7.tex @@ -1,17 +1,17 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep7}}\label{module-Ocamlary-module-Dep7}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep7}}\label{Ocamlary-Dep7}% \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-Dep7-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ -\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\ -\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{R}}}\\ +\label{Ocamlary-Dep7-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep7-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep7-argument-1-Arg-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ +\label{Ocamlary-Dep7-argument-1-Arg-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep7-argument-1-Arg-module-type-T-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-Dep7-argument-1-Arg-module-type-T-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{R}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-X-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\ -\label{module-Ocamlary-module-Dep7-argument-1-Arg-module-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{R}}}\\ +\label{Ocamlary-Dep7-argument-1-Arg-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep7-argument-1-Arg-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep7-argument-1-Arg-X-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-Dep7-argument-1-Arg-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} Y : \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-S]{\ocamlinlinecode{R}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-Dep7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep7-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-Dep7-argument-1-Arg-module-type-T]{\ocamlinlinecode{Arg.\allowbreak{}T}}}\\ +\label{Ocamlary-Dep7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep7-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \hyperref[Ocamlary-Dep7-argument-1-Arg-module-type-T]{\ocamlinlinecode{Arg.\allowbreak{}T}}}\\ \input{Ocamlary.Dep7.M.tex} diff --git a/test/generators/latex/Ocamlary.Dep9.tex b/test/generators/latex/Ocamlary.Dep9.tex index 4a1a826d45..d474392167 100644 --- a/test/generators/latex/Ocamlary.Dep9.tex +++ b/test/generators/latex/Ocamlary.Dep9.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep9}}\label{module-Ocamlary-module-Dep9}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep9}}\label{Ocamlary-Dep9}% \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-Dep9-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep9-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep9-argument-1-X-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\ +\label{Ocamlary-Dep9-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep9-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep9-argument-1-X-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-Dep9-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[module-Ocamlary-module-Dep9-argument-1-X-module-type-T]{\ocamlinlinecode{X.\allowbreak{}T}}}\\ +\label{Ocamlary-Dep9-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[Ocamlary-Dep9-argument-1-X-module-type-T]{\ocamlinlinecode{X.\allowbreak{}T}}}\\ diff --git a/test/generators/latex/Ocamlary.FunctorTypeOf.tex b/test/generators/latex/Ocamlary.FunctorTypeOf.tex index fe97f00d5a..e3577a02df 100644 --- a/test/generators/latex/Ocamlary.FunctorTypeOf.tex +++ b/test/generators/latex/Ocamlary.FunctorTypeOf.tex @@ -1,18 +1,18 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}FunctorTypeOf}}\label{module-Ocamlary-module-FunctorTypeOf}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}FunctorTypeOf}}\label{Ocamlary-FunctorTypeOf}% This comment is for \ocamlinlinecode{FunctorTypeOf}. \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection]{\ocamlinlinecode{Collection}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-FunctorTypeOf-argument-1-Collection}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection]{\ocamlinlinecode{Collection}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-FunctorTypeOf-argument-1-Collection-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-FunctorTypeOf-argument-1-Collection-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-FunctorTypeOf-argument-1-Collection-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -20,12 +20,12 @@ \subsection{Parameters\label{parameters}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-FunctorTypeOf-argument-1-Collection-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-FunctorTypeOf-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection-type-collection]{\ocamlinlinecode{Collection.\allowbreak{}collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-FunctorTypeOf-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection-type-collection]{\ocamlinlinecode{Collection.\allowbreak{}collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Ocamlary.ModuleWithSignature.tex b/test/generators/latex/Ocamlary.ModuleWithSignature.tex index 0ffe609d47..775352bb64 100644 --- a/test/generators/latex/Ocamlary.ModuleWithSignature.tex +++ b/test/generators/latex/Ocamlary.ModuleWithSignature.tex @@ -1,5 +1,5 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}ModuleWithSignature}}\label{module-Ocamlary-module-ModuleWithSignature}% -A plain module of a signature of \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{module-Ocamlary-module-type-EmptySig}]} (reference) +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}ModuleWithSignature}}\label{Ocamlary-ModuleWithSignature}% +A plain module of a signature of \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{Ocamlary-module-type-EmptySig}]} (reference) diff --git a/test/generators/latex/Ocamlary.ModuleWithSignatureAlias.tex b/test/generators/latex/Ocamlary.ModuleWithSignatureAlias.tex index 1520b73330..63dabe659b 100644 --- a/test/generators/latex/Ocamlary.ModuleWithSignatureAlias.tex +++ b/test/generators/latex/Ocamlary.ModuleWithSignatureAlias.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}ModuleWithSignatureAlias}}\label{module-Ocamlary-module-ModuleWithSignatureAlias}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}ModuleWithSignatureAlias}}\label{Ocamlary-ModuleWithSignatureAlias}% A plain module with an alias signature \begin{description}\kern-\topsep diff --git a/test/generators/latex/Ocamlary.Recollection.tex b/test/generators/latex/Ocamlary.Recollection.tex index ade30ac653..7e3ba0fb75 100644 --- a/test/generators/latex/Ocamlary.Recollection.tex +++ b/test/generators/latex/Ocamlary.Recollection.tex @@ -1,18 +1,18 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Recollection}}\label{module-Ocamlary-module-Recollection}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Recollection}}\label{Ocamlary-Recollection}% This comment is for \ocamlinlinecode{CollectionModule}. \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-Recollection-argument-1-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Recollection-argument-1-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-argument-1-C-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-Recollection-argument-1-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Recollection-argument-1-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-argument-1-C-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-argument-1-C-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-Recollection-argument-1-C-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-Recollection-argument-1-C-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Recollection-argument-1-C-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-argument-1-C-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-Recollection-argument-1-C-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -20,22 +20,22 @@ \subsection{Parameters\label{parameters}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-argument-1-C-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-Recollection-argument-1-C-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-Recollection-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-type-element]{\ocamlinlinecode{C.\allowbreak{}element}} list}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-Recollection-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection = \hyperref[Ocamlary-Recollection-argument-1-C-type-element]{\ocamlinlinecode{C.\allowbreak{}element}} list}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{C.\allowbreak{}collection}}}\\ -\label{module-Ocamlary-module-Recollection-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Recollection-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-Recollection-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-Recollection-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element = \hyperref[Ocamlary-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{C.\allowbreak{}collection}}}\\ +\label{Ocamlary-Recollection-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Recollection-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-Recollection-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-Recollection-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Recollection-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-Recollection-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-Recollection-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -43,7 +43,7 @@ \subsection{Signature\label{signature}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-Recollection-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-Recollection-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Ocamlary.With3.N.tex b/test/generators/latex/Ocamlary.With3.N.tex index 2d853c67f0..1c50b48ca1 100644 --- a/test/generators/latex/Ocamlary.With3.N.tex +++ b/test/generators/latex/Ocamlary.With3.N.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{With3.\allowbreak{}N}}\label{module-Ocamlary-module-With3-module-N}% -\label{module-Ocamlary-module-With3-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{With3.\allowbreak{}N}}\label{Ocamlary-With3-N}% +\label{Ocamlary-With3-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/generators/latex/Ocamlary.With3.tex b/test/generators/latex/Ocamlary.With3.tex index 3605791514..28ddbdd945 100644 --- a/test/generators/latex/Ocamlary.With3.tex +++ b/test/generators/latex/Ocamlary.With3.tex @@ -1,5 +1,5 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With3}}\label{module-Ocamlary-module-With3}% -\label{module-Ocamlary-module-With3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\\ -\label{module-Ocamlary-module-With3-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With3-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-With2-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\ +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With3}}\label{Ocamlary-With3}% +\label{Ocamlary-With3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[Ocamlary-With2]{\ocamlinlinecode{With2}}}\\ +\label{Ocamlary-With3-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With3-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[Ocamlary-With2-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\ \input{Ocamlary.With3.N.tex} diff --git a/test/generators/latex/Ocamlary.With4.N.tex b/test/generators/latex/Ocamlary.With4.N.tex index 0dfc5ccdcb..6e557810ae 100644 --- a/test/generators/latex/Ocamlary.With4.N.tex +++ b/test/generators/latex/Ocamlary.With4.N.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{With4.\allowbreak{}N}}\label{module-Ocamlary-module-With4-module-N}% -\label{module-Ocamlary-module-With4-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{With4.\allowbreak{}N}}\label{Ocamlary-With4-N}% +\label{Ocamlary-With4-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/generators/latex/Ocamlary.With4.tex b/test/generators/latex/Ocamlary.With4.tex index 8577e0bf06..b3d58e34c4 100644 --- a/test/generators/latex/Ocamlary.With4.tex +++ b/test/generators/latex/Ocamlary.With4.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With4}}\label{module-Ocamlary-module-With4}% -\label{module-Ocamlary-module-With4-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With4-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-With2-module-type-S]{\ocamlinlinecode{With2.\allowbreak{}S}}}\\ +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With4}}\label{Ocamlary-With4}% +\label{Ocamlary-With4-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With4-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[Ocamlary-With2-module-type-S]{\ocamlinlinecode{With2.\allowbreak{}S}}}\\ \input{Ocamlary.With4.N.tex} diff --git a/test/generators/latex/Ocamlary.With7.tex b/test/generators/latex/Ocamlary.With7.tex index 6322192634..f4a470d0c9 100644 --- a/test/generators/latex/Ocamlary.With7.tex +++ b/test/generators/latex/Ocamlary.With7.tex @@ -1,9 +1,9 @@ -\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With7}}\label{module-Ocamlary-module-With7}% +\section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}With7}}\label{Ocamlary-With7}% \subsection{Parameters\label{parameters}}% -\label{module-Ocamlary-module-With7-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With7-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With7-argument-1-X-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\ +\label{Ocamlary-With7-argument-1-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With7-argument-1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With7-argument-1-X-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{module-Ocamlary-module-With7-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[module-Ocamlary-module-With7-argument-1-X-module-type-T]{\ocamlinlinecode{X.\allowbreak{}T}}}\\ +\label{Ocamlary-With7-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} T = \hyperref[Ocamlary-With7-argument-1-X-module-type-T]{\ocamlinlinecode{X.\allowbreak{}T}}}\\ diff --git a/test/generators/latex/Ocamlary.empty_class.tex b/test/generators/latex/Ocamlary.empty_class.tex index 95789eefda..e35aa48b19 100644 --- a/test/generators/latex/Ocamlary.empty_class.tex +++ b/test/generators/latex/Ocamlary.empty_class.tex @@ -1,3 +1,3 @@ -\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}empty\_\allowbreak{}class}}\label{module-Ocamlary-class-empty_class}% +\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}empty\_\allowbreak{}class}}\label{Ocamlary-class-empty_class}% diff --git a/test/generators/latex/Ocamlary.one_method_class.tex b/test/generators/latex/Ocamlary.one_method_class.tex index b172b5b7e3..f51013fbd7 100644 --- a/test/generators/latex/Ocamlary.one_method_class.tex +++ b/test/generators/latex/Ocamlary.one_method_class.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}one\_\allowbreak{}method\_\allowbreak{}class}}\label{module-Ocamlary-class-one_method_class}% -\label{module-Ocamlary-class-one_method_class-method-go}\ocamlcodefragment{\ocamltag{keyword}{method} go : unit}\\ +\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}one\_\allowbreak{}method\_\allowbreak{}class}}\label{Ocamlary-class-one_method_class}% +\label{Ocamlary-class-one_method_class-method-go}\ocamlcodefragment{\ocamltag{keyword}{method} go : unit}\\ diff --git a/test/generators/latex/Ocamlary.param_class.tex b/test/generators/latex/Ocamlary.param_class.tex index 26a43760c5..5386ed4ac7 100644 --- a/test/generators/latex/Ocamlary.param_class.tex +++ b/test/generators/latex/Ocamlary.param_class.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}param\_\allowbreak{}class}}\label{module-Ocamlary-class-param_class}% -\label{module-Ocamlary-class-param_class-method-v}\ocamlcodefragment{\ocamltag{keyword}{method} v : \ocamltag{type-var}{'a}}\\ +\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}param\_\allowbreak{}class}}\label{Ocamlary-class-param_class}% +\label{Ocamlary-class-param_class-method-v}\ocamlcodefragment{\ocamltag{keyword}{method} v : \ocamltag{type-var}{'a}}\\ diff --git a/test/generators/latex/Ocamlary.tex b/test/generators/latex/Ocamlary.tex index 8daea9d864..3cf7bc5a1e 100644 --- a/test/generators/latex/Ocamlary.tex +++ b/test/generators/latex/Ocamlary.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Ocamlary}}\label{module-Ocamlary}% +\section{Module \ocamlinlinecode{Ocamlary}}\label{Ocamlary}% This is an \emph{interface} with \bold{all} of the \emph{module system} features. This documentation demonstrates: \begin{itemize}\item{comment formatting}% @@ -37,8 +37,8 @@ \section{Module \ocamlinlinecode{Ocamlary}}\label{module-Ocamlary}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{\hyperref[module-Ocamlary-module-Empty]{\ocamlinlinecode{\ocamlinlinecode{Empty}}[p\pageref*{module-Ocamlary-module-Empty}]}}]{A plain, empty module}% -\item[{\hyperref[module-Ocamlary-module-Empty]{\ocamlinlinecode{\ocamlinlinecode{EmptyAlias}}[p\pageref*{module-Ocamlary-module-Empty}]}}]{A plain module alias of \ocamlinlinecode{Empty}}\end{description}% +\item[{\hyperref[Ocamlary-Empty]{\ocamlinlinecode{\ocamlinlinecode{Empty}}[p\pageref*{Ocamlary-Empty}]}}]{A plain, empty module}% +\item[{\hyperref[Ocamlary-Empty]{\ocamlinlinecode{\ocamlinlinecode{EmptyAlias}}[p\pageref*{Ocamlary-Empty}]}}]{A plain module alias of \ocamlinlinecode{Empty}}\end{description}% Odoc doesn't support \ocamlinlinecode{\{!indexlist\}}. Here is some superscript: x\textsuperscript{2} @@ -56,64 +56,64 @@ \subsubsection{Level 2\label{level-2}}% \subsubsection{Level 3\label{level-3}}% \subsubsection{Level 4\label{level-4}}% \subsubsection{Basic module stuff\label{basic-module-stuff}}% -\label{module-Ocamlary-module-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-module-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A plain, empty module\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-Empty-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-Empty-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}An ambiguous, misnamed module type\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-MissingComment}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-MissingComment]{\ocamlinlinecode{MissingComment}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-MissingComment-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-MissingComment}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-MissingComment]{\ocamlinlinecode{MissingComment}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-MissingComment-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}An ambiguous, misnamed module type\end{ocamlindent}% \medbreak \subsection{Section 9000\label{s9000}}% -\label{module-Ocamlary-module-EmptyAlias}\ocamlcodefragment{\ocamltag{keyword}{module} EmptyAlias = \hyperref[module-Ocamlary-module-Empty]{\ocamlinlinecode{Empty}}}\begin{ocamlindent}A plain module alias of \ocamlinlinecode{Empty}\end{ocamlindent}% +\label{Ocamlary-module-EmptyAlias}\ocamlcodefragment{\ocamltag{keyword}{module} EmptyAlias = \hyperref[Ocamlary-Empty]{\ocamlinlinecode{Empty}}}\begin{ocamlindent}A plain module alias of \ocamlinlinecode{Empty}\end{ocamlindent}% \medbreak \subsubsection{EmptySig\label{emptySig}}% -\label{module-Ocamlary-module-type-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-module-type-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A plain, empty module signature\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-EmptySigAlias}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} EmptySigAlias = \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\begin{ocamlindent}A plain, empty module signature alias of\end{ocamlindent}% +\label{Ocamlary-module-type-EmptySigAlias}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} EmptySigAlias = \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\begin{ocamlindent}A plain, empty module signature alias of\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-ModuleWithSignature}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-ModuleWithSignature]{\ocamlinlinecode{ModuleWithSignature}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\begin{ocamlindent}A plain module of a signature of \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{module-Ocamlary-module-type-EmptySig}]} (reference)\end{ocamlindent}% +\label{Ocamlary-module-ModuleWithSignature}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-ModuleWithSignature]{\ocamlinlinecode{ModuleWithSignature}}}\ocamlcodefragment{ : \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\begin{ocamlindent}A plain module of a signature of \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{Ocamlary-module-type-EmptySig}]} (reference)\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-ModuleWithSignatureAlias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-ModuleWithSignatureAlias]{\ocamlinlinecode{ModuleWithSignatureAlias}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySigAlias}}}\begin{ocamlindent}A plain module with an alias signature\end{ocamlindent}% +\label{Ocamlary-module-ModuleWithSignatureAlias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-ModuleWithSignatureAlias]{\ocamlinlinecode{ModuleWithSignatureAlias}}}\ocamlcodefragment{ : \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySigAlias}}}\begin{ocamlindent}A plain module with an alias signature\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-One}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-One]{\ocamlinlinecode{One}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-One-type-one}\ocamlcodefragment{\ocamltag{keyword}{type} one}\\ +\label{Ocamlary-module-One}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-One]{\ocamlinlinecode{One}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-One-type-one}\ocamlcodefragment{\ocamltag{keyword}{type} one}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-SigForMod}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SigForMod]{\ocamlinlinecode{SigForMod}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-SigForMod-module-Inner}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-SigForMod-module-Inner]{\ocamlinlinecode{Inner}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-SigForMod-module-Inner-module-type-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SigForMod-module-Inner-module-type-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-module-type-SigForMod}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SigForMod]{\ocamlinlinecode{SigForMod}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-SigForMod-module-Inner}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-SigForMod-Inner]{\ocamlinlinecode{Inner}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-SigForMod-Inner-module-type-Empty}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SigForMod-Inner-module-type-Empty]{\ocamlinlinecode{Empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}There's a signature in a module in this signature.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-SuperSig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SuperSig]{\ocamlinlinecode{SuperSig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-SuperSig-module-type-SubSigA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigA]{\ocamlinlinecode{SubSigA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{A Labeled Section Header Inside of a Signature\label{subSig}}% -\label{module-Ocamlary-module-type-SuperSig-module-type-SubSigA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod]{\ocamlinlinecode{SubSigAMod}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod-type-sub_sig_a_mod}\ocamlcodefragment{\ocamltag{keyword}{type} sub\_\allowbreak{}sig\_\allowbreak{}a\_\allowbreak{}mod}\\ +\label{Ocamlary-module-type-SuperSig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SuperSig]{\ocamlinlinecode{SuperSig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-SuperSig-module-type-SubSigA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigA]{\ocamlinlinecode{SubSigA}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{A Labeled Section Header Inside of a Signature\label{subSig}}% +\label{Ocamlary-module-type-SuperSig-module-type-SubSigA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-SuperSig-module-type-SubSigA-module-SubSigAMod}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod]{\ocamlinlinecode{SubSigAMod}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod-type-sub_sig_a_mod}\ocamlcodefragment{\ocamltag{keyword}{type} sub\_\allowbreak{}sig\_\allowbreak{}a\_\allowbreak{}mod}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-SuperSig-module-type-SubSigB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigB]{\ocamlinlinecode{SubSigB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Another Labeled Section Header Inside of a Signature\label{subSig_2}}% -\label{module-Ocamlary-module-type-SuperSig-module-type-SubSigB-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-SuperSig-module-type-SubSigB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigB]{\ocamlinlinecode{SubSigB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Another Labeled Section Header Inside of a Signature\label{subSig_2}}% +\label{Ocamlary-module-type-SuperSig-module-type-SubSigB-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-SuperSig-module-type-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SuperSig-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-SuperSig-module-type-EmptySig-type-not_actually_empty}\ocamlcodefragment{\ocamltag{keyword}{type} not\_\allowbreak{}actually\_\allowbreak{}empty}\\ +\label{Ocamlary-module-type-SuperSig-module-type-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SuperSig-module-type-EmptySig]{\ocamlinlinecode{EmptySig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-SuperSig-module-type-EmptySig-type-not_actually_empty}\ocamlcodefragment{\ocamltag{keyword}{type} not\_\allowbreak{}actually\_\allowbreak{}empty}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-SuperSig-module-type-One}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SuperSig-module-type-One]{\ocamlinlinecode{One}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-SuperSig-module-type-One-type-two}\ocamlcodefragment{\ocamltag{keyword}{type} two}\\ +\label{Ocamlary-module-type-SuperSig-module-type-One}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SuperSig-module-type-One]{\ocamlinlinecode{One}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-SuperSig-module-type-One-type-two}\ocamlcodefragment{\ocamltag{keyword}{type} two}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-SuperSig-module-type-SuperSig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SuperSig]{\ocamlinlinecode{SuperSig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-module-type-SuperSig-module-type-SuperSig}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-SuperSig-module-type-SuperSig]{\ocamlinlinecode{SuperSig}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -For a good time, see \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig]{\ocamlinlinecode{A Labeled Section Header Inside of a Signature}[p\pageref*{module-Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig}]} or \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigB-subSig]{\ocamlinlinecode{Another Labeled Section Header Inside of a Signature}[p\pageref*{module-Ocamlary-module-type-SuperSig-module-type-SubSigB-subSig}]} or \hyperref[module-Ocamlary-module-type-SuperSig-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{SuperSig.\allowbreak{}EmptySig}}[p\pageref*{module-Ocamlary-module-type-SuperSig-module-type-EmptySig}]}. Section \hyperref[module-Ocamlary-s9000]{\ocamlinlinecode{Section 9000}[p\pageref*{module-Ocamlary-s9000}]} is also interesting. \hyperref[module-Ocamlary-emptySig]{\ocamlinlinecode{EmptySig}[p\pageref*{module-Ocamlary-emptySig}]} is the section and \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{module-Ocamlary-module-type-EmptySig}]} is the module signature. +For a good time, see \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig]{\ocamlinlinecode{A Labeled Section Header Inside of a Signature}[p\pageref*{Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig}]} or \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigB-subSig]{\ocamlinlinecode{Another Labeled Section Header Inside of a Signature}[p\pageref*{Ocamlary-module-type-SuperSig-module-type-SubSigB-subSig}]} or \hyperref[Ocamlary-module-type-SuperSig-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{SuperSig.\allowbreak{}EmptySig}}[p\pageref*{Ocamlary-module-type-SuperSig-module-type-EmptySig}]}. Section \hyperref[Ocamlary-s9000]{\ocamlinlinecode{Section 9000}[p\pageref*{Ocamlary-s9000}]} is also interesting. \hyperref[Ocamlary-emptySig]{\ocamlinlinecode{EmptySig}[p\pageref*{Ocamlary-emptySig}]} is the section and \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{Ocamlary-module-type-EmptySig}]} is the module signature. -\label{module-Ocamlary-module-Buffer}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Buffer]{\ocamlinlinecode{Buffer}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Buffer-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : int \ocamltag{arrow}{$\rightarrow$} unit}\\ +\label{Ocamlary-module-Buffer}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Buffer]{\ocamlinlinecode{Buffer}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Buffer-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : int \ocamltag{arrow}{$\rightarrow$} unit}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}References are resolved after everything, so \ocamlinlinecode{\{!Buffer.\allowbreak{}t\}} won't resolve.\end{ocamlindent}% \medbreak @@ -122,20 +122,20 @@ \subsubsection{EmptySig\label{emptySig}}% \subsubsection{Basic exception stuff\label{basic-exception-stuff}}% After exception title. -\label{module-Ocamlary-exception-Kaboom}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kaboom} \ocamltag{keyword}{of} unit}\begin{ocamlindent}Unary exception constructor\end{ocamlindent}% +\label{Ocamlary-exception-Kaboom}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kaboom} \ocamltag{keyword}{of} unit}\begin{ocamlindent}Unary exception constructor\end{ocamlindent}% \medbreak -\label{module-Ocamlary-exception-Kablam}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kablam} \ocamltag{keyword}{of} unit * unit}\begin{ocamlindent}Binary exception constructor\end{ocamlindent}% +\label{Ocamlary-exception-Kablam}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kablam} \ocamltag{keyword}{of} unit * unit}\begin{ocamlindent}Binary exception constructor\end{ocamlindent}% \medbreak -\label{module-Ocamlary-exception-Kapow}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kapow} \ocamltag{keyword}{of} unit * unit}\begin{ocamlindent}Unary exception constructor over binary tuple\end{ocamlindent}% +\label{Ocamlary-exception-Kapow}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Kapow} \ocamltag{keyword}{of} unit * unit}\begin{ocamlindent}Unary exception constructor over binary tuple\end{ocamlindent}% \medbreak -\label{module-Ocamlary-exception-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{EmptySig}}\begin{ocamlindent}\hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{module-Ocamlary-module-type-EmptySig}]} is a module and \hyperref[module-Ocamlary-exception-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{module-Ocamlary-exception-EmptySig}]} is this exception.\end{ocamlindent}% +\label{Ocamlary-exception-EmptySig}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{EmptySig}}\begin{ocamlindent}\hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{Ocamlary-module-type-EmptySig}]} is a module and \hyperref[Ocamlary-exception-EmptySig]{\ocamlinlinecode{\ocamlinlinecode{EmptySig}}[p\pageref*{Ocamlary-exception-EmptySig}]} is this exception.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-exception-EmptySigAlias}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{EmptySigAlias}}\begin{ocamlindent}\hyperref[module-Ocamlary-exception-EmptySigAlias]{\ocamlinlinecode{\ocamlinlinecode{EmptySigAlias}}[p\pageref*{module-Ocamlary-exception-EmptySigAlias}]} is this exception.\end{ocamlindent}% +\label{Ocamlary-exception-EmptySigAlias}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{EmptySigAlias}}\begin{ocamlindent}\hyperref[Ocamlary-exception-EmptySigAlias]{\ocamlinlinecode{\ocamlinlinecode{EmptySigAlias}}[p\pageref*{Ocamlary-exception-EmptySigAlias}]} is this exception.\end{ocamlindent}% \medbreak \subsubsection{Basic type and value stuff with advanced doc comments\label{basic-type-and-value-stuff-with-advanced-doc-comments}}% -\label{module-Ocamlary-type-a_function}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) a\_\allowbreak{}function = \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}}\begin{ocamlindent}\hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{\ocamlinlinecode{a\_\allowbreak{}function}}[p\pageref*{module-Ocamlary-type-a_function}]} is this type and \hyperref[module-Ocamlary-val-a_function]{\ocamlinlinecode{\ocamlinlinecode{a\_\allowbreak{}function}}[p\pageref*{module-Ocamlary-val-a_function}]} is the value below.\end{ocamlindent}% +\label{Ocamlary-type-a_function}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) a\_\allowbreak{}function = \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}}\begin{ocamlindent}\hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{\ocamlinlinecode{a\_\allowbreak{}function}}[p\pageref*{Ocamlary-type-a_function}]} is this type and \hyperref[Ocamlary-val-a_function]{\ocamlinlinecode{\ocamlinlinecode{a\_\allowbreak{}function}}[p\pageref*{Ocamlary-val-a_function}]} is the value below.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-a_function}\ocamlcodefragment{\ocamltag{keyword}{val} a\_\allowbreak{}function : \ocamltag{label}{x}:int \ocamltag{arrow}{$\rightarrow$} int}\begin{ocamlindent}This is \ocamlinlinecode{a\_\allowbreak{}function} with param and return type.\begin{description}\kern-\topsep +\label{Ocamlary-val-a_function}\ocamlcodefragment{\ocamltag{keyword}{val} a\_\allowbreak{}function : \ocamltag{label}{x}:int \ocamltag{arrow}{$\rightarrow$} int}\begin{ocamlindent}This is \ocamlinlinecode{a\_\allowbreak{}function} with param and return type.\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{parameter x}]{the \ocamlinlinecode{x} coordinate}\end{description}% \begin{description}\kern-\topsep @@ -143,39 +143,39 @@ \subsubsection{Basic type and value stuff with advanced doc comments\label{basic \item[{returns}]{the \ocamlinlinecode{y} coordinate}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-fun_fun_fun}\ocamlcodefragment{\ocamltag{keyword}{val} fun\_\allowbreak{}fun\_\allowbreak{}fun : ((int,\allowbreak{} int) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}},\allowbreak{} (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\\ -\label{module-Ocamlary-val-fun_maybe}\ocamlcodefragment{\ocamltag{keyword}{val} fun\_\allowbreak{}maybe : \ocamltag{optlabel}{?yes}:unit \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} int}\\ -\label{module-Ocamlary-val-not_found}\ocamlcodefragment{\ocamltag{keyword}{val} not\_\allowbreak{}found : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Ocamlary-val-fun_fun_fun}\ocamlcodefragment{\ocamltag{keyword}{val} fun\_\allowbreak{}fun\_\allowbreak{}fun : ((int,\allowbreak{} int) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}},\allowbreak{} (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\\ +\label{Ocamlary-val-fun_maybe}\ocamlcodefragment{\ocamltag{keyword}{val} fun\_\allowbreak{}maybe : \ocamltag{optlabel}{?yes}:unit \ocamltag{arrow}{$\rightarrow$} unit \ocamltag{arrow}{$\rightarrow$} int}\\ +\label{Ocamlary-val-not_found}\ocamlcodefragment{\ocamltag{keyword}{val} not\_\allowbreak{}found : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{raises \ocamlinlinecode{Not\_\allowbreak{}found}}]{That's all it does}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-kaboom}\ocamlcodefragment{\ocamltag{keyword}{val} kaboom : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Ocamlary-val-kaboom}\ocamlcodefragment{\ocamltag{keyword}{val} kaboom : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{raises \hyperref[module-Ocamlary-exception-Kaboom]{\ocamlinlinecode{\ocamlinlinecode{Kaboom}}}}]{That's all it does}\end{description}% +\item[{raises \hyperref[Ocamlary-exception-Kaboom]{\ocamlinlinecode{\ocamlinlinecode{Kaboom}}}}]{That's all it does}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-ocaml_org}\ocamlcodefragment{\ocamltag{keyword}{val} ocaml\_\allowbreak{}org : string}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Ocamlary-val-ocaml_org}\ocamlcodefragment{\ocamltag{keyword}{val} ocaml\_\allowbreak{}org : string}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{see \href{http://ocaml.org/}{http://ocaml.org/}\footnote{\url{http://ocaml.org/}}}]{The OCaml Web site}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-some_file}\ocamlcodefragment{\ocamltag{keyword}{val} some\_\allowbreak{}file : string}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Ocamlary-val-some_file}\ocamlcodefragment{\ocamltag{keyword}{val} some\_\allowbreak{}file : string}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{see \ocamlinlinecode{some\_\allowbreak{}file}}]{The file called \ocamlinlinecode{some\_\allowbreak{}file}}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-some_doc}\ocamlcodefragment{\ocamltag{keyword}{val} some\_\allowbreak{}doc : string}\begin{ocamlindent}\begin{description}\kern-\topsep +\label{Ocamlary-val-some_doc}\ocamlcodefragment{\ocamltag{keyword}{val} some\_\allowbreak{}doc : string}\begin{ocamlindent}\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{see some\_\allowbreak{}doc}]{The document called \ocamlinlinecode{some\_\allowbreak{}doc}}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-since_mesozoic}\ocamlcodefragment{\ocamltag{keyword}{val} since\_\allowbreak{}mesozoic : unit}\begin{ocamlindent}This value was introduced in the Mesozoic era.\begin{description}\kern-\topsep +\label{Ocamlary-val-since_mesozoic}\ocamlcodefragment{\ocamltag{keyword}{val} since\_\allowbreak{}mesozoic : unit}\begin{ocamlindent}This value was introduced in the Mesozoic era.\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{since}]{mesozoic}\end{description}% \end{ocamlindent}% \medbreak -\label{module-Ocamlary-val-changing}\ocamlcodefragment{\ocamltag{keyword}{val} changing : unit}\begin{ocamlindent}This value has had changes in 1.0.0, 1.1.0, and 1.2.0.\begin{description}\kern-\topsep +\label{Ocamlary-val-changing}\ocamlcodefragment{\ocamltag{keyword}{val} changing : unit}\begin{ocamlindent}This value has had changes in 1.0.0, 1.1.0, and 1.2.0.\begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[{before 1.\allowbreak{}0.\allowbreak{}0}]{before 1.0.0}\end{description}% \begin{description}\kern-\topsep @@ -187,32 +187,32 @@ \subsubsection{Basic type and value stuff with advanced doc comments\label{basic \end{ocamlindent}% \medbreak \subsubsection{Some Operators\label{some-operators}}% -\label{module-Ocamlary-val-(+t+-)}\ocamlcodefragment{\ocamltag{keyword}{val} (\textasciitilde{}-) : unit}\\ -\label{module-Ocamlary-val-(!)}\ocamlcodefragment{\ocamltag{keyword}{val} (!) : unit}\\ -\label{module-Ocamlary-val-(@)}\ocamlcodefragment{\ocamltag{keyword}{val} (@) : unit}\\ -\label{module-Ocamlary-val-($)}\ocamlcodefragment{\ocamltag{keyword}{val} (\$) : unit}\\ -\label{module-Ocamlary-val-(+p+)}\ocamlcodefragment{\ocamltag{keyword}{val} (\%) : unit}\\ -\label{module-Ocamlary-val-(+a+)}\ocamlcodefragment{\ocamltag{keyword}{val} (\&) : unit}\\ -\label{module-Ocamlary-val-(*)}\ocamlcodefragment{\ocamltag{keyword}{val} (*) : unit}\\ -\label{module-Ocamlary-val-(-)}\ocamlcodefragment{\ocamltag{keyword}{val} (-) : unit}\\ -\label{module-Ocamlary-val-(+++)}\ocamlcodefragment{\ocamltag{keyword}{val} (+) : unit}\\ -\label{module-Ocamlary-val-(-?)}\ocamlcodefragment{\ocamltag{keyword}{val} (-?) : unit}\\ -\label{module-Ocamlary-val-(/)}\ocamlcodefragment{\ocamltag{keyword}{val} (/) : unit}\\ -\label{module-Ocamlary-val-(:=)}\ocamlcodefragment{\ocamltag{keyword}{val} (:=) : unit}\\ -\label{module-Ocamlary-val-(=)}\ocamlcodefragment{\ocamltag{keyword}{val} (=) : unit}\\ -\label{module-Ocamlary-val-(land)}\ocamlcodefragment{\ocamltag{keyword}{val} (land) : unit}\\ +\label{Ocamlary-val-(+t+-)}\ocamlcodefragment{\ocamltag{keyword}{val} (\textasciitilde{}-) : unit}\\ +\label{Ocamlary-val-(!)}\ocamlcodefragment{\ocamltag{keyword}{val} (!) : unit}\\ +\label{Ocamlary-val-(@)}\ocamlcodefragment{\ocamltag{keyword}{val} (@) : unit}\\ +\label{Ocamlary-val-($)}\ocamlcodefragment{\ocamltag{keyword}{val} (\$) : unit}\\ +\label{Ocamlary-val-(+p+)}\ocamlcodefragment{\ocamltag{keyword}{val} (\%) : unit}\\ +\label{Ocamlary-val-(+a+)}\ocamlcodefragment{\ocamltag{keyword}{val} (\&) : unit}\\ +\label{Ocamlary-val-(*)}\ocamlcodefragment{\ocamltag{keyword}{val} (*) : unit}\\ +\label{Ocamlary-val-(-)}\ocamlcodefragment{\ocamltag{keyword}{val} (-) : unit}\\ +\label{Ocamlary-val-(+++)}\ocamlcodefragment{\ocamltag{keyword}{val} (+) : unit}\\ +\label{Ocamlary-val-(-?)}\ocamlcodefragment{\ocamltag{keyword}{val} (-?) : unit}\\ +\label{Ocamlary-val-(/)}\ocamlcodefragment{\ocamltag{keyword}{val} (/) : unit}\\ +\label{Ocamlary-val-(:=)}\ocamlcodefragment{\ocamltag{keyword}{val} (:=) : unit}\\ +\label{Ocamlary-val-(=)}\ocamlcodefragment{\ocamltag{keyword}{val} (=) : unit}\\ +\label{Ocamlary-val-(land)}\ocamlcodefragment{\ocamltag{keyword}{val} (land) : unit}\\ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% -\label{module-Ocamlary-module-CollectionModule}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CollectionModule]{\ocamlinlinecode{CollectionModule}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CollectionModule-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-module-CollectionModule}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CollectionModule]{\ocamlinlinecode{CollectionModule}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CollectionModule-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-CollectionModule-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-CollectionModule-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CollectionModule-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CollectionModule-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-CollectionModule-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-CollectionModule-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-CollectionModule-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CollectionModule-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CollectionModule-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-CollectionModule-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-CollectionModule-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CollectionModule-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -220,22 +220,22 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-CollectionModule-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-CollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-CollectionModule-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-COLLECTION}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-COLLECTION-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-module-type-COLLECTION}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-COLLECTION-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-COLLECTION-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-type-COLLECTION-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-COLLECTION-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-COLLECTION-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-COLLECTION-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-module-type-COLLECTION-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-COLLECTION-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-COLLECTION-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-COLLECTION-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-COLLECTION-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -243,28 +243,28 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-COLLECTION-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-type-COLLECTION-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-module-type-COLLECTION-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}module type of\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-Recollection}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Recollection]{\ocamlinlinecode{Recollection}}}\ocamlcodefragment{ - (\hyperref[module-Ocamlary-module-Recollection-argument-1-C]{\ocamlinlinecode{C}} : \hyperref[module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}}) : - \hyperref[module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}} - \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-COLLECTION-type-collection]{\ocamlinlinecode{collection}} = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-type-element]{\ocamlinlinecode{C.\allowbreak{}element}} list - \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-COLLECTION-type-element]{\ocamlinlinecode{element}} = \hyperref[module-Ocamlary-module-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{C.\allowbreak{}collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% +\label{Ocamlary-module-Recollection}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Recollection]{\ocamlinlinecode{Recollection}}}\ocamlcodefragment{ + (\hyperref[Ocamlary-Recollection-argument-1-C]{\ocamlinlinecode{C}} : \hyperref[Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}}) : + \hyperref[Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}} + \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-COLLECTION-type-collection]{\ocamlinlinecode{collection}} = \hyperref[Ocamlary-Recollection-argument-1-C-type-element]{\ocamlinlinecode{C.\allowbreak{}element}} list + \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-COLLECTION-type-element]{\ocamlinlinecode{element}} = \hyperref[Ocamlary-Recollection-argument-1-C-type-collection]{\ocamlinlinecode{C.\allowbreak{}collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-MMM}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-MMM]{\ocamlinlinecode{MMM}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-MMM-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-MMM-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-MMM-module-C-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-module-type-MMM}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-MMM]{\ocamlinlinecode{MMM}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-MMM-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-MMM-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-MMM-C-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-MMM-module-C-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-MMM-module-C-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-MMM-C-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-module-type-MMM-C-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-MMM-C-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-MMM-C-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-MMM-C-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-MMM-C-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -272,26 +272,26 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-MMM-module-C-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-type-MMM-module-C-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-module-type-MMM-C-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-RECOLLECTION}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-RECOLLECTION]{\ocamlinlinecode{RECOLLECTION}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-RECOLLECTION-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[module-Ocamlary-module-Recollection]{\ocamlinlinecode{Recollection(CollectionModule)}}}\\ +\label{Ocamlary-module-type-RECOLLECTION}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-RECOLLECTION]{\ocamlinlinecode{RECOLLECTION}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-RECOLLECTION-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[Ocamlary-Recollection]{\ocamlinlinecode{Recollection(CollectionModule)}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-RecollectionModule}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-RecollectionModule]{\ocamlinlinecode{RecollectionModule}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}\label{module-Ocamlary-module-type-RecollectionModule-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection = \hyperref[module-Ocamlary-module-CollectionModule-type-element]{\ocamlinlinecode{CollectionModule.\allowbreak{}element}} list}\\ -\label{module-Ocamlary-module-type-RecollectionModule-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element = \hyperref[module-Ocamlary-module-CollectionModule-type-collection]{\ocamlinlinecode{CollectionModule.\allowbreak{}collection}}}\\ -\label{module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-RecollectionModule-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-RecollectionModule}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-RecollectionModule]{\ocamlinlinecode{RecollectionModule}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}\label{Ocamlary-module-type-RecollectionModule-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection = \hyperref[Ocamlary-CollectionModule-type-element]{\ocamlinlinecode{CollectionModule.\allowbreak{}element}} list}\\ +\label{Ocamlary-module-type-RecollectionModule-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element = \hyperref[Ocamlary-CollectionModule-type-collection]{\ocamlinlinecode{CollectionModule.\allowbreak{}collection}}}\\ +\label{Ocamlary-module-type-RecollectionModule-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-RecollectionModule-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-RecollectionModule-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-RecollectionModule-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-RecollectionModule-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -299,22 +299,22 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-RecollectionModule-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-type-RecollectionModule-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-module-type-RecollectionModule-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-A}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Ocamlary-module-type-A-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-A-module-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-A-module-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-module-type-A}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-A-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-A-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-A-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-A-module-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-type-A-module-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-A-module-Q-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-A-module-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-A-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-module-type-A-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-A-Q-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-A-Q-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-A-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-A-Q-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -322,25 +322,25 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-A-module-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-type-A-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-module-type-A-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-B}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Ocamlary-module-type-B-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-B-module-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-B-module-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-module-type-B}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-B-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-B-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-B-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-B-module-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-type-B-module-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-B-module-Q-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-B-module-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-B-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-module-type-B-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-B-Q-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-B-Q-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-B-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-B-Q-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -348,25 +348,25 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-B-module-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-type-B-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-module-type-B-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-C}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-A]{\ocamlinlinecode{A}}\label{module-Ocamlary-module-type-C-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Ocamlary-module-type-C-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-C-module-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-C-module-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% +\label{Ocamlary-module-type-C}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-A]{\ocamlinlinecode{A}}\label{Ocamlary-module-type-C-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-C-module-Q}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-C-Q]{\ocamlinlinecode{Q}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-C-Q-type-collection}\ocamlcodefragment{\ocamltag{keyword}{type} collection}\begin{ocamlindent}This comment is for \ocamlinlinecode{collection}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-C-module-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ -\label{module-Ocamlary-module-type-C-module-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-C-module-Q-module-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-C-module-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-C-Q-type-element}\ocamlcodefragment{\ocamltag{keyword}{type} element}\\ +\label{Ocamlary-module-type-C-Q-module-InnerModuleA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-C-Q-InnerModuleA]{\ocamlinlinecode{InnerModuleA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-C-Q-InnerModuleA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-C-Q-type-collection]{\ocamlinlinecode{collection}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-C-Q-InnerModuleA-module-InnerModuleA'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA']{\ocamlinlinecode{InnerModuleA'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-a_function]{\ocamlinlinecode{a\_\allowbreak{}function}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA'}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% +\label{Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleTypeA'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'-type-t]{\ocamlinlinecode{InnerModuleA'.\allowbreak{}t}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{t}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA'}.\end{ocamlindent}% @@ -374,394 +374,394 @@ \subsubsection{Advanced Module Stuff\label{advanced-module-stuff}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleA}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-C-module-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[module-Ocamlary-module-type-C-module-Q-module-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% +\label{Ocamlary-module-type-C-Q-module-type-InnerModuleTypeA}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} InnerModuleTypeA = \hyperref[Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA']{\ocamlinlinecode{InnerModuleA.\allowbreak{}InnerModuleTypeA'}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{InnerModuleTypeA}.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{CollectionModule}.\end{ocamlindent}% \medbreak -\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-B]{\ocamlinlinecode{B}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-B-type-t]{\ocamlinlinecode{t}} := \hyperref[module-Ocamlary-module-type-C-type-t]{\ocamlinlinecode{t}} \ocamltag{keyword}{and} \ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-B-module-Q]{\ocamlinlinecode{Q}} := \hyperref[module-Ocamlary-module-type-C-module-Q]{\ocamlinlinecode{Q}}\end{ocamlindent}% +\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-B]{\ocamlinlinecode{B}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-B-type-t]{\ocamlinlinecode{t}} := \hyperref[Ocamlary-module-type-C-type-t]{\ocamlinlinecode{t}} \ocamltag{keyword}{and} \ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-B-Q]{\ocamlinlinecode{Q}} := \hyperref[Ocamlary-module-type-C-Q]{\ocamlinlinecode{Q}}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This module type includes two signatures.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-FunctorTypeOf}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-FunctorTypeOf]{\ocamlinlinecode{FunctorTypeOf}}}\ocamlcodefragment{ - (\hyperref[module-Ocamlary-module-FunctorTypeOf-argument-1-Collection]{\ocamlinlinecode{Collection}} : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-CollectionModule]{\ocamlinlinecode{CollectionModule}}) : +\label{Ocamlary-module-FunctorTypeOf}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-FunctorTypeOf]{\ocamlinlinecode{FunctorTypeOf}}}\ocamlcodefragment{ + (\hyperref[Ocamlary-FunctorTypeOf-argument-1-Collection]{\ocamlinlinecode{Collection}} : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-CollectionModule]{\ocamlinlinecode{CollectionModule}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{FunctorTypeOf}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-IncludeModuleType}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-IncludeModuleType]{\ocamlinlinecode{IncludeModuleType}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{include EmptySigAlias}.\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySigAlias}}\end{ocamlindent}% +\label{Ocamlary-module-type-IncludeModuleType}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-IncludeModuleType]{\ocamlinlinecode{IncludeModuleType}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}This comment is for \ocamlinlinecode{include EmptySigAlias}.\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-EmptySig]{\ocamlinlinecode{EmptySigAlias}}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This comment is for \ocamlinlinecode{IncludeModuleType}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-module-type-ToInclude}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-ToInclude]{\ocamlinlinecode{ToInclude}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-ToInclude-module-IncludedA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-ToInclude-module-IncludedA]{\ocamlinlinecode{IncludedA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-ToInclude-module-IncludedA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-ToInclude}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-ToInclude]{\ocamlinlinecode{ToInclude}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-ToInclude-module-IncludedA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-ToInclude-IncludedA]{\ocamlinlinecode{IncludedA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-ToInclude-IncludedA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-ToInclude-module-type-IncludedB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-ToInclude-module-type-IncludedB]{\ocamlinlinecode{IncludedB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-ToInclude-module-type-IncludedB-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s}\\ +\label{Ocamlary-module-type-ToInclude-module-type-IncludedB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-ToInclude-module-type-IncludedB]{\ocamlinlinecode{IncludedB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-ToInclude-module-type-IncludedB-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-ToInclude]{\ocamlinlinecode{ToInclude}}\label{module-Ocamlary-module-IncludedA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-IncludedA]{\ocamlinlinecode{IncludedA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-IncludedA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-ToInclude]{\ocamlinlinecode{ToInclude}}\label{Ocamlary-module-IncludedA}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-IncludedA]{\ocamlinlinecode{IncludedA}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-IncludedA-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-IncludedB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-IncludedB]{\ocamlinlinecode{IncludedB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-IncludedB-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s}\\ +\label{Ocamlary-module-type-IncludedB}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-IncludedB]{\ocamlinlinecode{IncludedB}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-IncludedB-type-s}\ocamlcodefragment{\ocamltag{keyword}{type} s}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Advanced Type Stuff\label{advanced-type-stuff}}% -\label{module-Ocamlary-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{field1 : int;\allowbreak{}}\label{module-Ocamlary-type-record.field1}& This comment is for \ocamlinlinecode{field1}.\\ -\ocamlinlinecode{field2 : int;\allowbreak{}}\label{module-Ocamlary-type-record.field2}& This comment is for \ocamlinlinecode{field2}.\\ +\label{Ocamlary-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{field1 : int;\allowbreak{}}\label{Ocamlary-type-record.field1}& This comment is for \ocamlinlinecode{field1}.\\ +\ocamlinlinecode{field2 : int;\allowbreak{}}\label{Ocamlary-type-record.field2}& This comment is for \ocamlinlinecode{field2}.\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\begin{ocamlindent}This comment is for \ocamlinlinecode{record}.This comment is also for \ocamlinlinecode{record}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-mutable_record}\ocamlcodefragment{\ocamltag{keyword}{type} mutable\_\allowbreak{}record = \{}\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{\ocamltag{keyword}{mutable} a : int;\allowbreak{}}\label{module-Ocamlary-type-mutable_record.a}& \ocamlinlinecode{a} is first and mutable\\ -\ocamlinlinecode{b : unit;\allowbreak{}}\label{module-Ocamlary-type-mutable_record.b}& \ocamlinlinecode{b} is second and immutable\\ -\ocamlinlinecode{\ocamltag{keyword}{mutable} c : int;\allowbreak{}}\label{module-Ocamlary-type-mutable_record.c}& \ocamlinlinecode{c} is third and mutable\\ +\label{Ocamlary-type-mutable_record}\ocamlcodefragment{\ocamltag{keyword}{type} mutable\_\allowbreak{}record = \{}\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{\ocamltag{keyword}{mutable} a : int;\allowbreak{}}\label{Ocamlary-type-mutable_record.a}& \ocamlinlinecode{a} is first and mutable\\ +\ocamlinlinecode{b : unit;\allowbreak{}}\label{Ocamlary-type-mutable_record.b}& \ocamlinlinecode{b} is second and immutable\\ +\ocamlinlinecode{\ocamltag{keyword}{mutable} c : int;\allowbreak{}}\label{Ocamlary-type-mutable_record.c}& \ocamlinlinecode{c} is third and mutable\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\\ -\label{module-Ocamlary-type-universe_record}\ocamlcodefragment{\ocamltag{keyword}{type} universe\_\allowbreak{}record = \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{nihilate : 'a.\allowbreak{} \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit;\allowbreak{}}\label{module-Ocamlary-type-universe_record.nihilate}\\ +\label{Ocamlary-type-universe_record}\ocamlcodefragment{\ocamltag{keyword}{type} universe\_\allowbreak{}record = \{}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{nihilate : 'a.\allowbreak{} \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} unit;\allowbreak{}}\label{Ocamlary-type-universe_record.nihilate}\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\\ -\label{module-Ocamlary-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{TagA}}\label{module-Ocamlary-type-variant.TagA}& This comment is for \ocamlinlinecode{TagA}.\\ -\ocamlcodefragment{| \ocamltag{constructor}{ConstrB} \ocamltag{keyword}{of} int}\label{module-Ocamlary-type-variant.ConstrB}& This comment is for \ocamlinlinecode{ConstrB}.\\ -\ocamlcodefragment{| \ocamltag{constructor}{ConstrC} \ocamltag{keyword}{of} int * int}\label{module-Ocamlary-type-variant.ConstrC}& This comment is for binary \ocamlinlinecode{ConstrC}.\\ -\ocamlcodefragment{| \ocamltag{constructor}{ConstrD} \ocamltag{keyword}{of} int * int}\label{module-Ocamlary-type-variant.ConstrD}& This comment is for unary \ocamlinlinecode{ConstrD} of binary tuple.\\ +\label{Ocamlary-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{TagA}}\label{Ocamlary-type-variant.TagA}& This comment is for \ocamlinlinecode{TagA}.\\ +\ocamlcodefragment{| \ocamltag{constructor}{ConstrB} \ocamltag{keyword}{of} int}\label{Ocamlary-type-variant.ConstrB}& This comment is for \ocamlinlinecode{ConstrB}.\\ +\ocamlcodefragment{| \ocamltag{constructor}{ConstrC} \ocamltag{keyword}{of} int * int}\label{Ocamlary-type-variant.ConstrC}& This comment is for binary \ocamlinlinecode{ConstrC}.\\ +\ocamlcodefragment{| \ocamltag{constructor}{ConstrD} \ocamltag{keyword}{of} int * int}\label{Ocamlary-type-variant.ConstrD}& This comment is for unary \ocamlinlinecode{ConstrD} of binary tuple.\\ \end{ocamltabular}% \\ \begin{ocamlindent}This comment is for \ocamlinlinecode{variant}.This comment is also for \ocamlinlinecode{variant}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} poly\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `TagA}\label{module-Ocamlary-type-poly_variant.TagA}\\ -\ocamlcodefragment{| `ConstrB \ocamltag{keyword}{of} int}\label{module-Ocamlary-type-poly_variant.ConstrB}\\ +\label{Ocamlary-type-poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} poly\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `TagA}\label{Ocamlary-type-poly_variant.TagA}\\ +\ocamlcodefragment{| `ConstrB \ocamltag{keyword}{of} int}\label{Ocamlary-type-poly_variant.ConstrB}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\begin{ocamlindent}This comment is for \ocamlinlinecode{poly\_\allowbreak{}variant}.Wow! It was a polymorphic variant!\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-full_gadt}\ocamlcodefragment{\ocamltag{keyword}{type} (\_\allowbreak{},\allowbreak{} \_\allowbreak{}) full\_\allowbreak{}gadt = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Tag} : (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-full_gadt.Tag}\\ -\ocamlcodefragment{| \ocamltag{constructor}{First} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'a},\allowbreak{} unit) \hyperref[module-Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-full_gadt.First}\\ -\ocamlcodefragment{| \ocamltag{constructor}{Second} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (unit,\allowbreak{} \ocamltag{type-var}{'a}) \hyperref[module-Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-full_gadt.Second}\\ -\ocamlcodefragment{| \ocamltag{constructor}{Exist} : \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'b},\allowbreak{} unit) \hyperref[module-Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-full_gadt.Exist}\\ +\label{Ocamlary-type-full_gadt}\ocamlcodefragment{\ocamltag{keyword}{type} (\_\allowbreak{},\allowbreak{} \_\allowbreak{}) full\_\allowbreak{}gadt = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Tag} : (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{Ocamlary-type-full_gadt.Tag}\\ +\ocamlcodefragment{| \ocamltag{constructor}{First} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'a},\allowbreak{} unit) \hyperref[Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{Ocamlary-type-full_gadt.First}\\ +\ocamlcodefragment{| \ocamltag{constructor}{Second} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (unit,\allowbreak{} \ocamltag{type-var}{'a}) \hyperref[Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{Ocamlary-type-full_gadt.Second}\\ +\ocamlcodefragment{| \ocamltag{constructor}{Exist} : \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'b},\allowbreak{} unit) \hyperref[Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}}}\label{Ocamlary-type-full_gadt.Exist}\\ \end{ocamltabular}% \\ \begin{ocamlindent}This comment is for \ocamlinlinecode{full\_\allowbreak{}gadt}.Wow! It was a GADT!\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-partial_gadt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a partial\_\allowbreak{}gadt = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{AscribeTag} : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-partial_gadt.AscribeTag}\\ -\ocamlcodefragment{| \ocamltag{constructor}{OfTag} \ocamltag{keyword}{of} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-partial_gadt.OfTag}\\ -\ocamlcodefragment{| \ocamltag{constructor}{ExistGadtTag} : (\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}) \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{module-Ocamlary-type-partial_gadt.ExistGadtTag}\\ +\label{Ocamlary-type-partial_gadt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a partial\_\allowbreak{}gadt = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{AscribeTag} : \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{Ocamlary-type-partial_gadt.AscribeTag}\\ +\ocamlcodefragment{| \ocamltag{constructor}{OfTag} \ocamltag{keyword}{of} \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{Ocamlary-type-partial_gadt.OfTag}\\ +\ocamlcodefragment{| \ocamltag{constructor}{ExistGadtTag} : (\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}) \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}}}\label{Ocamlary-type-partial_gadt.ExistGadtTag}\\ \end{ocamltabular}% \\ \begin{ocamlindent}This comment is for \ocamlinlinecode{partial\_\allowbreak{}gadt}.Wow! It was a mixed GADT!\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = \hyperref[module-Ocamlary-type-variant]{\ocamlinlinecode{variant}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{alias}.\end{ocamlindent}% +\label{Ocamlary-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = \hyperref[Ocamlary-type-variant]{\ocamlinlinecode{variant}}}\begin{ocamlindent}This comment is for \ocamlinlinecode{alias}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-tuple}\ocamlcodefragment{\ocamltag{keyword}{type} tuple = (\hyperref[module-Ocamlary-type-alias]{\ocamlinlinecode{alias}} * \hyperref[module-Ocamlary-type-alias]{\ocamlinlinecode{alias}}) * \hyperref[module-Ocamlary-type-alias]{\ocamlinlinecode{alias}} * (\hyperref[module-Ocamlary-type-alias]{\ocamlinlinecode{alias}} * \hyperref[module-Ocamlary-type-alias]{\ocamlinlinecode{alias}})}\begin{ocamlindent}This comment is for \ocamlinlinecode{tuple}.\end{ocamlindent}% +\label{Ocamlary-type-tuple}\ocamlcodefragment{\ocamltag{keyword}{type} tuple = (\hyperref[Ocamlary-type-alias]{\ocamlinlinecode{alias}} * \hyperref[Ocamlary-type-alias]{\ocamlinlinecode{alias}}) * \hyperref[Ocamlary-type-alias]{\ocamlinlinecode{alias}} * (\hyperref[Ocamlary-type-alias]{\ocamlinlinecode{alias}} * \hyperref[Ocamlary-type-alias]{\ocamlinlinecode{alias}})}\begin{ocamlindent}This comment is for \ocamlinlinecode{tuple}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-variant_alias}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}alias = \hyperref[module-Ocamlary-type-variant]{\ocamlinlinecode{variant}} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{TagA}}\label{module-Ocamlary-type-variant_alias.TagA}\\ -\ocamlcodefragment{| \ocamltag{constructor}{ConstrB} \ocamltag{keyword}{of} int}\label{module-Ocamlary-type-variant_alias.ConstrB}\\ -\ocamlcodefragment{| \ocamltag{constructor}{ConstrC} \ocamltag{keyword}{of} int * int}\label{module-Ocamlary-type-variant_alias.ConstrC}\\ -\ocamlcodefragment{| \ocamltag{constructor}{ConstrD} \ocamltag{keyword}{of} int * int}\label{module-Ocamlary-type-variant_alias.ConstrD}\\ +\label{Ocamlary-type-variant_alias}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}alias = \hyperref[Ocamlary-type-variant]{\ocamlinlinecode{variant}} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{TagA}}\label{Ocamlary-type-variant_alias.TagA}\\ +\ocamlcodefragment{| \ocamltag{constructor}{ConstrB} \ocamltag{keyword}{of} int}\label{Ocamlary-type-variant_alias.ConstrB}\\ +\ocamlcodefragment{| \ocamltag{constructor}{ConstrC} \ocamltag{keyword}{of} int * int}\label{Ocamlary-type-variant_alias.ConstrC}\\ +\ocamlcodefragment{| \ocamltag{constructor}{ConstrD} \ocamltag{keyword}{of} int * int}\label{Ocamlary-type-variant_alias.ConstrD}\\ \end{ocamltabular}% \\ \begin{ocamlindent}This comment is for \ocamlinlinecode{variant\_\allowbreak{}alias}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-record_alias}\ocamlcodefragment{\ocamltag{keyword}{type} record\_\allowbreak{}alias = \hyperref[module-Ocamlary-type-record]{\ocamlinlinecode{record}} = \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field1 : int;\allowbreak{}}\label{module-Ocamlary-type-record_alias.field1}\\ -\ocamlinlinecode{field2 : int;\allowbreak{}}\label{module-Ocamlary-type-record_alias.field2}\\ +\label{Ocamlary-type-record_alias}\ocamlcodefragment{\ocamltag{keyword}{type} record\_\allowbreak{}alias = \hyperref[Ocamlary-type-record]{\ocamlinlinecode{record}} = \{}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field1 : int;\allowbreak{}}\label{Ocamlary-type-record_alias.field1}\\ +\ocamlinlinecode{field2 : int;\allowbreak{}}\label{Ocamlary-type-record_alias.field2}\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\begin{ocamlindent}This comment is for \ocamlinlinecode{record\_\allowbreak{}alias}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-poly_variant_union}\ocamlcodefragment{\ocamltag{keyword}{type} poly\_\allowbreak{}variant\_\allowbreak{}union = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \hyperref[module-Ocamlary-type-poly_variant]{\ocamlinlinecode{poly\_\allowbreak{}variant}}}\label{module-Ocamlary-type-poly_variant_union.poly_variant}\\ -\ocamlcodefragment{| `TagC}\label{module-Ocamlary-type-poly_variant_union.TagC}\\ +\label{Ocamlary-type-poly_variant_union}\ocamlcodefragment{\ocamltag{keyword}{type} poly\_\allowbreak{}variant\_\allowbreak{}union = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \hyperref[Ocamlary-type-poly_variant]{\ocamlinlinecode{poly\_\allowbreak{}variant}}}\label{Ocamlary-type-poly_variant_union.poly_variant}\\ +\ocamlcodefragment{| `TagC}\label{Ocamlary-type-poly_variant_union.TagC}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\begin{ocamlindent}This comment is for \ocamlinlinecode{poly\_\allowbreak{}variant\_\allowbreak{}union}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-poly_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `TagA \ocamltag{keyword}{of} \ocamltag{type-var}{'a}}\label{module-Ocamlary-type-poly_poly_variant.TagA}\\ +\label{Ocamlary-type-poly_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `TagA \ocamltag{keyword}{of} \ocamltag{type-var}{'a}}\label{Ocamlary-type-poly_poly_variant.TagA}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Ocamlary-type-bin_poly_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) bin\_\allowbreak{}poly\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `TagA \ocamltag{keyword}{of} \ocamltag{type-var}{'a}}\label{module-Ocamlary-type-bin_poly_poly_variant.TagA}\\ -\ocamlcodefragment{| `ConstrB \ocamltag{keyword}{of} \ocamltag{type-var}{'b}}\label{module-Ocamlary-type-bin_poly_poly_variant.ConstrB}\\ +\label{Ocamlary-type-bin_poly_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) bin\_\allowbreak{}poly\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `TagA \ocamltag{keyword}{of} \ocamltag{type-var}{'a}}\label{Ocamlary-type-bin_poly_poly_variant.TagA}\\ +\ocamlcodefragment{| `ConstrB \ocamltag{keyword}{of} \ocamltag{type-var}{'b}}\label{Ocamlary-type-bin_poly_poly_variant.ConstrB}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Ocamlary-type-open_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant = [> `TagA ] \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-type-open_poly_variant2}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant2 = [> `ConstrB of int ] \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-type-open_poly_variant_alias}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant\_\allowbreak{}alias = \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-open_poly_variant]{\ocamlinlinecode{open\_\allowbreak{}poly\_\allowbreak{}variant}} \hyperref[module-Ocamlary-type-open_poly_variant2]{\ocamlinlinecode{open\_\allowbreak{}poly\_\allowbreak{}variant2}}}\\ -\label{module-Ocamlary-type-poly_fun}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}fun = [> `ConstrB of int ] \ocamltag{keyword}{as} 'a \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a}}\\ -\label{module-Ocamlary-type-poly_fun_constraint}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}fun\_\allowbreak{}constraint = \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `TagA ]}\\ -\label{module-Ocamlary-type-closed_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a closed\_\allowbreak{}poly\_\allowbreak{}variant = [< `One | `Two ] \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-type-clopen_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a clopen\_\allowbreak{}poly\_\allowbreak{}variant = [< `One | `Two of int | `Three Two Three ] \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-type-nested_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A}\label{module-Ocamlary-type-nested_poly_variant.A}\\ -\ocamlcodefragment{| `B \ocamltag{keyword}{of} [ `B1 | `B2 ]}\label{module-Ocamlary-type-nested_poly_variant.B}\\ -\ocamlcodefragment{| `C}\label{module-Ocamlary-type-nested_poly_variant.C}\\ -\ocamlcodefragment{| `D \ocamltag{keyword}{of} [ `D1 of [ `D1a ] ]}\label{module-Ocamlary-type-nested_poly_variant.D}\\ +\label{Ocamlary-type-open_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant = [> `TagA ] \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-type-open_poly_variant2}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant2 = [> `ConstrB of int ] \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-type-open_poly_variant_alias}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}poly\_\allowbreak{}variant\_\allowbreak{}alias = \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-open_poly_variant]{\ocamlinlinecode{open\_\allowbreak{}poly\_\allowbreak{}variant}} \hyperref[Ocamlary-type-open_poly_variant2]{\ocamlinlinecode{open\_\allowbreak{}poly\_\allowbreak{}variant2}}}\\ +\label{Ocamlary-type-poly_fun}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}fun = [> `ConstrB of int ] \ocamltag{keyword}{as} 'a \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a}}\\ +\label{Ocamlary-type-poly_fun_constraint}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}fun\_\allowbreak{}constraint = \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `TagA ]}\\ +\label{Ocamlary-type-closed_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a closed\_\allowbreak{}poly\_\allowbreak{}variant = [< `One | `Two ] \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-type-clopen_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a clopen\_\allowbreak{}poly\_\allowbreak{}variant = [< `One | `Two of int | `Three Two Three ] \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-type-nested_poly_variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}poly\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A}\label{Ocamlary-type-nested_poly_variant.A}\\ +\ocamlcodefragment{| `B \ocamltag{keyword}{of} [ `B1 | `B2 ]}\label{Ocamlary-type-nested_poly_variant.B}\\ +\ocamlcodefragment{| `C}\label{Ocamlary-type-nested_poly_variant.C}\\ +\ocamlcodefragment{| `D \ocamltag{keyword}{of} [ `D1 of [ `D1a ] ]}\label{Ocamlary-type-nested_poly_variant.D}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Ocamlary-type-full_gadt_alias}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) full\_\allowbreak{}gadt\_\allowbreak{}alias = (\ocamltag{type-var}{'a},\allowbreak{} \ocamltag{type-var}{'b}) \hyperref[module-Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Tag} : (unit,\allowbreak{} unit) \hyperref[module-Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-full_gadt_alias.Tag}\\ -\ocamlcodefragment{| \ocamltag{constructor}{First} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'a},\allowbreak{} unit) \hyperref[module-Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-full_gadt_alias.First}\\ -\ocamlcodefragment{| \ocamltag{constructor}{Second} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (unit,\allowbreak{} \ocamltag{type-var}{'a}) \hyperref[module-Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-full_gadt_alias.Second}\\ -\ocamlcodefragment{| \ocamltag{constructor}{Exist} : \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'b},\allowbreak{} unit) \hyperref[module-Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-full_gadt_alias.Exist}\\ +\label{Ocamlary-type-full_gadt_alias}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) full\_\allowbreak{}gadt\_\allowbreak{}alias = (\ocamltag{type-var}{'a},\allowbreak{} \ocamltag{type-var}{'b}) \hyperref[Ocamlary-type-full_gadt]{\ocamlinlinecode{full\_\allowbreak{}gadt}} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Tag} : (unit,\allowbreak{} unit) \hyperref[Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-full_gadt_alias.Tag}\\ +\ocamlcodefragment{| \ocamltag{constructor}{First} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'a},\allowbreak{} unit) \hyperref[Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-full_gadt_alias.First}\\ +\ocamlcodefragment{| \ocamltag{constructor}{Second} : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} (unit,\allowbreak{} \ocamltag{type-var}{'a}) \hyperref[Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-full_gadt_alias.Second}\\ +\ocamlcodefragment{| \ocamltag{constructor}{Exist} : \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{arrow}{$\rightarrow$} (\ocamltag{type-var}{'b},\allowbreak{} unit) \hyperref[Ocamlary-type-full_gadt_alias]{\ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-full_gadt_alias.Exist}\\ \end{ocamltabular}% \\ \begin{ocamlindent}This comment is for \ocamlinlinecode{full\_\allowbreak{}gadt\_\allowbreak{}alias}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-partial_gadt_alias}\ocamlcodefragment{\ocamltag{keyword}{type} 'a partial\_\allowbreak{}gadt\_\allowbreak{}alias = \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{AscribeTag} : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt_alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-partial_gadt_alias.AscribeTag}\\ -\ocamlcodefragment{| \ocamltag{constructor}{OfTag} \ocamltag{keyword}{of} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt_alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-partial_gadt_alias.OfTag}\\ -\ocamlcodefragment{| \ocamltag{constructor}{ExistGadtTag} : (\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}) \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-type-partial_gadt_alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{module-Ocamlary-type-partial_gadt_alias.ExistGadtTag}\\ +\label{Ocamlary-type-partial_gadt_alias}\ocamlcodefragment{\ocamltag{keyword}{type} 'a partial\_\allowbreak{}gadt\_\allowbreak{}alias = \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt]{\ocamlinlinecode{partial\_\allowbreak{}gadt}} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{AscribeTag} : \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt_alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-partial_gadt_alias.AscribeTag}\\ +\ocamlcodefragment{| \ocamltag{constructor}{OfTag} \ocamltag{keyword}{of} \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt_alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-partial_gadt_alias.OfTag}\\ +\ocamlcodefragment{| \ocamltag{constructor}{ExistGadtTag} : (\ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'b}) \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[Ocamlary-type-partial_gadt_alias]{\ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}}}\label{Ocamlary-type-partial_gadt_alias.ExistGadtTag}\\ \end{ocamltabular}% \\ \begin{ocamlindent}This comment is for \ocamlinlinecode{partial\_\allowbreak{}gadt\_\allowbreak{}alias}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-exception-Exn_arrow}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Exn\_\allowbreak{}arrow} : unit \ocamltag{arrow}{$\rightarrow$} exn}\begin{ocamlindent}This comment is for \hyperref[module-Ocamlary-exception-Exn_arrow]{\ocamlinlinecode{\ocamlinlinecode{Exn\_\allowbreak{}arrow}}[p\pageref*{module-Ocamlary-exception-Exn_arrow}]}.\end{ocamlindent}% +\label{Ocamlary-exception-Exn_arrow}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Exn\_\allowbreak{}arrow} : unit \ocamltag{arrow}{$\rightarrow$} exn}\begin{ocamlindent}This comment is for \hyperref[Ocamlary-exception-Exn_arrow]{\ocamlinlinecode{\ocamlinlinecode{Exn\_\allowbreak{}arrow}}[p\pageref*{Ocamlary-exception-Exn_arrow}]}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-mutual_constr_a}\ocamlcodefragment{\ocamltag{keyword}{type} mutual\_\allowbreak{}constr\_\allowbreak{}a = }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{module-Ocamlary-type-mutual_constr_a.A}& \\ -\ocamlcodefragment{| \ocamltag{constructor}{B\_\allowbreak{}ish} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}}\label{module-Ocamlary-type-mutual_constr_a.B_ish}& This comment is between \hyperref[module-Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{module-Ocamlary-type-mutual_constr_a}]} and \hyperref[module-Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{module-Ocamlary-type-mutual_constr_b}]}.\\ +\label{Ocamlary-type-mutual_constr_a}\ocamlcodefragment{\ocamltag{keyword}{type} mutual\_\allowbreak{}constr\_\allowbreak{}a = }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{Ocamlary-type-mutual_constr_a.A}& \\ +\ocamlcodefragment{| \ocamltag{constructor}{B\_\allowbreak{}ish} \ocamltag{keyword}{of} \hyperref[Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}}\label{Ocamlary-type-mutual_constr_a.B_ish}& This comment is between \hyperref[Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{Ocamlary-type-mutual_constr_a}]} and \hyperref[Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{Ocamlary-type-mutual_constr_b}]}.\\ \end{ocamltabular}% \\ -\begin{ocamlindent}This comment is for \hyperref[module-Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{module-Ocamlary-type-mutual_constr_a}]} then \hyperref[module-Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{module-Ocamlary-type-mutual_constr_b}]}.\end{ocamlindent}% +\begin{ocamlindent}This comment is for \hyperref[Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{Ocamlary-type-mutual_constr_a}]} then \hyperref[Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{Ocamlary-type-mutual_constr_b}]}.\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-mutual_constr_b}\ocamlcodefragment{\ocamltag{keyword}{and} mutual\_\allowbreak{}constr\_\allowbreak{}b = }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{module-Ocamlary-type-mutual_constr_b.B}& \\ -\ocamlcodefragment{| \ocamltag{constructor}{A\_\allowbreak{}ish} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}}\label{module-Ocamlary-type-mutual_constr_b.A_ish}& This comment must be here for the next to associate correctly.\\ +\label{Ocamlary-type-mutual_constr_b}\ocamlcodefragment{\ocamltag{keyword}{and} mutual\_\allowbreak{}constr\_\allowbreak{}b = }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{Ocamlary-type-mutual_constr_b.B}& \\ +\ocamlcodefragment{| \ocamltag{constructor}{A\_\allowbreak{}ish} \ocamltag{keyword}{of} \hyperref[Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}}\label{Ocamlary-type-mutual_constr_b.A_ish}& This comment must be here for the next to associate correctly.\\ \end{ocamltabular}% \\ -\begin{ocamlindent}This comment is for \hyperref[module-Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{module-Ocamlary-type-mutual_constr_b}]} then \hyperref[module-Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{module-Ocamlary-type-mutual_constr_a}]}.\end{ocamlindent}% -\medbreak -\label{module-Ocamlary-type-rec_obj}\ocamlcodefragment{\ocamltag{keyword}{type} rec\_\allowbreak{}obj = < f : int ;\allowbreak{} g : unit \ocamltag{arrow}{$\rightarrow$} unit ;\allowbreak{} h : \hyperref[module-Ocamlary-type-rec_obj]{\ocamlinlinecode{rec\_\allowbreak{}obj}} >}\\ -\label{module-Ocamlary-type-open_obj}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}obj = < f : int ;\allowbreak{} g : unit \ocamltag{arrow}{$\rightarrow$} unit.\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-type-oof}\ocamlcodefragment{\ocamltag{keyword}{type} 'a oof = < a : unit.\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a}}\\ -\label{module-Ocamlary-type-any_obj}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}obj = < .\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-type-empty_obj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}obj = < >}\\ -\label{module-Ocamlary-type-one_meth}\ocamlcodefragment{\ocamltag{keyword}{type} one\_\allowbreak{}meth = < meth : unit >}\\ -\label{module-Ocamlary-type-ext}\ocamlcodefragment{\ocamltag{keyword}{type} ext = .\allowbreak{}.\allowbreak{}}\begin{ocamlindent}A mystery wrapped in an ellipsis\end{ocamlindent}% -\medbreak -\label{module-Ocamlary-extension-decl-ExtA}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtA}}\label{module-Ocamlary-extension-ExtA}\\ +\begin{ocamlindent}This comment is for \hyperref[Ocamlary-type-mutual_constr_b]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}b}}[p\pageref*{Ocamlary-type-mutual_constr_b}]} then \hyperref[Ocamlary-type-mutual_constr_a]{\ocamlinlinecode{\ocamlinlinecode{mutual\_\allowbreak{}constr\_\allowbreak{}a}}[p\pageref*{Ocamlary-type-mutual_constr_a}]}.\end{ocamlindent}% +\medbreak +\label{Ocamlary-type-rec_obj}\ocamlcodefragment{\ocamltag{keyword}{type} rec\_\allowbreak{}obj = < f : int ;\allowbreak{} g : unit \ocamltag{arrow}{$\rightarrow$} unit ;\allowbreak{} h : \hyperref[Ocamlary-type-rec_obj]{\ocamlinlinecode{rec\_\allowbreak{}obj}} >}\\ +\label{Ocamlary-type-open_obj}\ocamlcodefragment{\ocamltag{keyword}{type} 'a open\_\allowbreak{}obj = < f : int ;\allowbreak{} g : unit \ocamltag{arrow}{$\rightarrow$} unit.\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-type-oof}\ocamlcodefragment{\ocamltag{keyword}{type} 'a oof = < a : unit.\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a}}\\ +\label{Ocamlary-type-any_obj}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}obj = < .\allowbreak{}.\allowbreak{} > \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-type-empty_obj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}obj = < >}\\ +\label{Ocamlary-type-one_meth}\ocamlcodefragment{\ocamltag{keyword}{type} one\_\allowbreak{}meth = < meth : unit >}\\ +\label{Ocamlary-type-ext}\ocamlcodefragment{\ocamltag{keyword}{type} ext = .\allowbreak{}.\allowbreak{}}\begin{ocamlindent}A mystery wrapped in an ellipsis\end{ocamlindent}% +\medbreak +\label{Ocamlary-extension-decl-ExtA}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtA}}\label{Ocamlary-extension-ExtA}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-extension-decl-ExtB}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtB}}\label{module-Ocamlary-extension-ExtB}\\ +\label{Ocamlary-extension-decl-ExtB}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtB}}\label{Ocamlary-extension-ExtB}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-extension-decl-ExtC}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtC} \ocamltag{keyword}{of} unit}\label{module-Ocamlary-extension-ExtC}\\ -\ocamlcodefragment{| \ocamltag{extension}{ExtD} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-type-ext]{\ocamlinlinecode{ext}}}\label{module-Ocamlary-extension-ExtD}\\ +\label{Ocamlary-extension-decl-ExtC}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtC} \ocamltag{keyword}{of} unit}\label{Ocamlary-extension-ExtC}\\ +\ocamlcodefragment{| \ocamltag{extension}{ExtD} \ocamltag{keyword}{of} \hyperref[Ocamlary-type-ext]{\ocamlinlinecode{ext}}}\label{Ocamlary-extension-ExtD}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-extension-decl-ExtE}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtE}}\label{module-Ocamlary-extension-ExtE}\\ +\label{Ocamlary-extension-decl-ExtE}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-ext]{\ocamlinlinecode{ext}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtE}}\label{Ocamlary-extension-ExtE}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-extension-decl-ExtF}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-ext]{\ocamlinlinecode{ext}} += \ocamltag{keyword}{private} }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtF}}\label{module-Ocamlary-extension-ExtF}\\ +\label{Ocamlary-extension-decl-ExtF}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-ext]{\ocamlinlinecode{ext}} += \ocamltag{keyword}{private} }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ExtF}}\label{Ocamlary-extension-ExtF}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-type-poly_ext}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}ext = .\allowbreak{}.\allowbreak{}}\begin{ocamlindent}'a poly\_ext\end{ocamlindent}% +\label{Ocamlary-type-poly_ext}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}ext = .\allowbreak{}.\allowbreak{}}\begin{ocamlindent}'a poly\_ext\end{ocamlindent}% \medbreak -\label{module-Ocamlary-extension-decl-Foo}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-poly_ext]{\ocamlinlinecode{poly\_\allowbreak{}ext}} += }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Foo} \ocamltag{keyword}{of} \ocamltag{type-var}{'b}}\label{module-Ocamlary-extension-Foo}& \\ -\ocamlcodefragment{| \ocamltag{extension}{Bar} \ocamltag{keyword}{of} \ocamltag{type-var}{'b} * \ocamltag{type-var}{'b}}\label{module-Ocamlary-extension-Bar}& 'b poly\_ext\\ +\label{Ocamlary-extension-decl-Foo}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-poly_ext]{\ocamlinlinecode{poly\_\allowbreak{}ext}} += }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Foo} \ocamltag{keyword}{of} \ocamltag{type-var}{'b}}\label{Ocamlary-extension-Foo}& \\ +\ocamlcodefragment{| \ocamltag{extension}{Bar} \ocamltag{keyword}{of} \ocamltag{type-var}{'b} * \ocamltag{type-var}{'b}}\label{Ocamlary-extension-Bar}& 'b poly\_ext\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-extension-decl-Quux}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-poly_ext]{\ocamlinlinecode{poly\_\allowbreak{}ext}} += }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Quux} \ocamltag{keyword}{of} \ocamltag{type-var}{'c}}\label{module-Ocamlary-extension-Quux}& 'c poly\_ext\\ +\label{Ocamlary-extension-decl-Quux}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-poly_ext]{\ocamlinlinecode{poly\_\allowbreak{}ext}} += }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Quux} \ocamltag{keyword}{of} \ocamltag{type-var}{'c}}\label{Ocamlary-extension-Quux}& 'c poly\_ext\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-module-ExtMod}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-ExtMod]{\ocamlinlinecode{ExtMod}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-ExtMod-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = .\allowbreak{}.\allowbreak{}}\\ -\label{module-Ocamlary-module-ExtMod-extension-decl-Leisureforce}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-ExtMod-type-t]{\ocamlinlinecode{t}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Leisureforce}}\label{module-Ocamlary-module-ExtMod-extension-Leisureforce}\\ +\label{Ocamlary-module-ExtMod}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-ExtMod]{\ocamlinlinecode{ExtMod}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-ExtMod-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = .\allowbreak{}.\allowbreak{}}\\ +\label{Ocamlary-ExtMod-extension-decl-Leisureforce}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-ExtMod-type-t]{\ocamlinlinecode{t}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Leisureforce}}\label{Ocamlary-ExtMod-extension-Leisureforce}\\ \end{ocamltabular}% \\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-extension-decl-ZzzTop0}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-ExtMod-type-t]{\ocamlinlinecode{ExtMod.\allowbreak{}t}} += }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ZzzTop0}}\label{module-Ocamlary-extension-ZzzTop0}& It's got the rock\\ +\label{Ocamlary-extension-decl-ZzzTop0}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-ExtMod-type-t]{\ocamlinlinecode{ExtMod.\allowbreak{}t}} += }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ZzzTop0}}\label{Ocamlary-extension-ZzzTop0}& It's got the rock\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-extension-decl-ZzzTop}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-ExtMod-type-t]{\ocamlinlinecode{ExtMod.\allowbreak{}t}} += }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ZzzTop} \ocamltag{keyword}{of} unit}\label{module-Ocamlary-extension-ZzzTop}& and it packs a unit.\\ +\label{Ocamlary-extension-decl-ZzzTop}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-ExtMod-type-t]{\ocamlinlinecode{ExtMod.\allowbreak{}t}} += }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{ZzzTop} \ocamltag{keyword}{of} unit}\label{Ocamlary-extension-ZzzTop}& and it packs a unit.\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-val-launch_missiles}\ocamlcodefragment{\ocamltag{keyword}{val} launch\_\allowbreak{}missiles : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Rotate keys on my mark...\end{ocamlindent}% +\label{Ocamlary-val-launch_missiles}\ocamlcodefragment{\ocamltag{keyword}{val} launch\_\allowbreak{}missiles : unit \ocamltag{arrow}{$\rightarrow$} unit}\begin{ocamlindent}Rotate keys on my mark...\end{ocamlindent}% \medbreak -\label{module-Ocamlary-type-my_mod}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}mod = (\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}})}\begin{ocamlindent}A brown paper package tied up with string\end{ocamlindent}% +\label{Ocamlary-type-my_mod}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}mod = (\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}})}\begin{ocamlindent}A brown paper package tied up with string\end{ocamlindent}% \medbreak -\label{module-Ocamlary-class-empty_class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-empty_class]{\ocamlinlinecode{empty\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-class-one_method_class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-one_method_class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-class-two_method_class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-two_method_class]{\ocamlinlinecode{two\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-class-param_class}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[module-Ocamlary-class-param_class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-type-my_unit_object}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}unit\_\allowbreak{}object = unit \hyperref[module-Ocamlary-class-param_class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\\ -\label{module-Ocamlary-type-my_unit_class}\ocamlcodefragment{\ocamltag{keyword}{type} 'a my\_\allowbreak{}unit\_\allowbreak{}class = unit \hyperref[module-Ocamlary-class-param_class]{\ocamlinlinecode{param\_\allowbreak{}class}} \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-module-Dep1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep1]{\ocamlinlinecode{Dep1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep1-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep1-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ +\label{Ocamlary-class-empty_class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Ocamlary-class-empty_class]{\ocamlinlinecode{empty\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-class-one_method_class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Ocamlary-class-one_method_class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-class-two_method_class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Ocamlary-class-two_method_class]{\ocamlinlinecode{two\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-class-param_class}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[Ocamlary-class-param_class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-type-my_unit_object}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}unit\_\allowbreak{}object = unit \hyperref[Ocamlary-class-param_class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\\ +\label{Ocamlary-type-my_unit_class}\ocamlcodefragment{\ocamltag{keyword}{type} 'a my\_\allowbreak{}unit\_\allowbreak{}class = unit \hyperref[Ocamlary-class-param_class]{\ocamlinlinecode{param\_\allowbreak{}class}} \ocamltag{keyword}{as} 'a}\\ +\label{Ocamlary-module-Dep1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep1]{\ocamlinlinecode{Dep1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep1-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep1-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep1-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Ocamlary-Dep1-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{Ocamlary-Dep1-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep1-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep1-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep1-module-X-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-Dep1-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-Dep1-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep1-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep1-X-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep1-X-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \hyperref[Ocamlary-Dep1-module-type-S]{\ocamlinlinecode{S}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep2]{\ocamlinlinecode{Dep2}}}\ocamlcodefragment{ (\hyperref[module-Ocamlary-module-Dep2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-type-dep1}\ocamlcodefragment{\ocamltag{keyword}{type} dep1 = \hyperref[module-Ocamlary-module-Dep1-module-type-S-class-c]{\ocamlinlinecode{Dep2(Dep1).\allowbreak{}B.\allowbreak{}c}}}\\ -\label{module-Ocamlary-module-Dep3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep3]{\ocamlinlinecode{Dep3}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep3-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\ +\label{Ocamlary-module-Dep2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep2]{\ocamlinlinecode{Dep2}}}\ocamlcodefragment{ (\hyperref[Ocamlary-Dep2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-type-dep1}\ocamlcodefragment{\ocamltag{keyword}{type} dep1 = \hyperref[Ocamlary-Dep1-module-type-S-class-c]{\ocamlinlinecode{Dep2(Dep1).\allowbreak{}B.\allowbreak{}c}}}\\ +\label{Ocamlary-module-Dep3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep3]{\ocamlinlinecode{Dep3}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep3-type-a}\ocamlcodefragment{\ocamltag{keyword}{type} a}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep4]{\ocamlinlinecode{Dep4}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep4-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep4-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep4-module-type-T-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ +\label{Ocamlary-module-Dep4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep4]{\ocamlinlinecode{Dep4}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep4-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep4-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep4-module-type-T-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep4-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep4-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep4-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep4-module-type-S-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep4-module-type-S-module-X-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ +\label{Ocamlary-Dep4-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep4-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep4-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep4-module-type-S-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep4-module-type-S-X-type-b}\ocamlcodefragment{\ocamltag{keyword}{type} b}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep4-module-type-S-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep4-module-type-S-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-Dep4-module-type-S-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep4-module-type-S-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep4-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep4-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-Dep4-module-type-T]{\ocamlinlinecode{T}}}\\ +\label{Ocamlary-Dep4-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep4-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \hyperref[Ocamlary-Dep4-module-type-T]{\ocamlinlinecode{T}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep5]{\ocamlinlinecode{Dep5}}}\ocamlcodefragment{ (\hyperref[module-Ocamlary-module-Dep5-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-type-dep2}\ocamlcodefragment{\ocamltag{keyword}{type} dep2 = \hyperref[module-Ocamlary-module-Dep4-module-type-T-type-b]{\ocamlinlinecode{Dep5(Dep4).\allowbreak{}Z.\allowbreak{}X.\allowbreak{}b}}}\\ -\label{module-Ocamlary-type-dep3}\ocamlcodefragment{\ocamltag{keyword}{type} dep3 = \hyperref[module-Ocamlary-module-Dep3-type-a]{\ocamlinlinecode{Dep5(Dep4).\allowbreak{}Z.\allowbreak{}Y.\allowbreak{}a}}}\\ -\label{module-Ocamlary-module-Dep6}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep6]{\ocamlinlinecode{Dep6}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep6-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep6-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep6-module-type-S-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\ +\label{Ocamlary-module-Dep5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep5]{\ocamlinlinecode{Dep5}}}\ocamlcodefragment{ (\hyperref[Ocamlary-Dep5-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-type-dep2}\ocamlcodefragment{\ocamltag{keyword}{type} dep2 = \hyperref[Ocamlary-Dep4-module-type-T-type-b]{\ocamlinlinecode{Dep5(Dep4).\allowbreak{}Z.\allowbreak{}X.\allowbreak{}b}}}\\ +\label{Ocamlary-type-dep3}\ocamlcodefragment{\ocamltag{keyword}{type} dep3 = \hyperref[Ocamlary-Dep3-type-a]{\ocamlinlinecode{Dep5(Dep4).\allowbreak{}Z.\allowbreak{}Y.\allowbreak{}a}}}\\ +\label{Ocamlary-module-Dep6}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep6]{\ocamlinlinecode{Dep6}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep6-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep6-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep6-module-type-S-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep6-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep6-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep6-module-type-T-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[module-Ocamlary-module-Dep6-module-type-S]{\ocamlinlinecode{S}}}\\ -\label{module-Ocamlary-module-Dep6-module-type-T-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep6-module-type-T-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep6-module-type-T-module-Y-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\ +\label{Ocamlary-Dep6-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep6-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep6-module-type-T-module-type-R}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} R = \hyperref[Ocamlary-Dep6-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-Dep6-module-type-T-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep6-module-type-T-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep6-module-type-T-Y-type-d}\ocamlcodefragment{\ocamltag{keyword}{type} d}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep6-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep6-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-Dep6-module-type-T]{\ocamlinlinecode{T}}}\\ +\label{Ocamlary-Dep6-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep6-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \hyperref[Ocamlary-Dep6-module-type-T]{\ocamlinlinecode{T}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep7}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep7]{\ocamlinlinecode{Dep7}}}\ocamlcodefragment{ (\hyperref[module-Ocamlary-module-Dep7-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-type-dep4}\ocamlcodefragment{\ocamltag{keyword}{type} dep4 = \hyperref[module-Ocamlary-module-Dep6-module-type-T-module-Y-type-d]{\ocamlinlinecode{Dep7(Dep6).\allowbreak{}M.\allowbreak{}Y.\allowbreak{}d}}}\\ -\label{module-Ocamlary-module-Dep8}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep8]{\ocamlinlinecode{Dep8}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep8-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep8-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep8-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-Dep7}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep7]{\ocamlinlinecode{Dep7}}}\ocamlcodefragment{ (\hyperref[Ocamlary-Dep7-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-type-dep4}\ocamlcodefragment{\ocamltag{keyword}{type} dep4 = \hyperref[Ocamlary-Dep6-module-type-T-Y-type-d]{\ocamlinlinecode{Dep7(Dep6).\allowbreak{}M.\allowbreak{}Y.\allowbreak{}d}}}\\ +\label{Ocamlary-module-Dep8}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep8]{\ocamlinlinecode{Dep8}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep8-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep8-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep8-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep9}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep9]{\ocamlinlinecode{Dep9}}}\ocamlcodefragment{ (\hyperref[module-Ocamlary-module-Dep9-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-Dep10}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-Dep10]{\ocamlinlinecode{Dep10}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-Dep10-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ +\label{Ocamlary-module-Dep9}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep9]{\ocamlinlinecode{Dep9}}}\ocamlcodefragment{ (\hyperref[Ocamlary-Dep9-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-module-type-Dep10}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-Dep10]{\ocamlinlinecode{Dep10}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-Dep10-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep11}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep11]{\ocamlinlinecode{Dep11}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep11-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep11-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ +\label{Ocamlary-module-Dep11}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep11]{\ocamlinlinecode{Dep11}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep11-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-Dep11-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Dep11-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Ocamlary-Dep11-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{Ocamlary-Dep11-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep12}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep12]{\ocamlinlinecode{Dep12}}}\ocamlcodefragment{ (\hyperref[module-Ocamlary-module-Dep12-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep13}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep13]{\ocamlinlinecode{Dep13}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-Dep11-module-type-S]{\ocamlinlinecode{Dep12(Dep11).\allowbreak{}T}}}\\ -\label{module-Ocamlary-type-dep5}\ocamlcodefragment{\ocamltag{keyword}{type} dep5 = \hyperref[module-Ocamlary-module-Dep11-module-type-S-class-c]{\ocamlinlinecode{Dep13.\allowbreak{}c}}}\\ -\label{module-Ocamlary-module-type-With1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-With1]{\ocamlinlinecode{With1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With1-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-With1-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With1-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ +\label{Ocamlary-module-Dep12}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep12]{\ocamlinlinecode{Dep12}}}\ocamlcodefragment{ (\hyperref[Ocamlary-Dep12-argument-1-Arg]{\ocamlinlinecode{Arg}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-module-Dep13}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Dep13]{\ocamlinlinecode{Dep13}}}\ocamlcodefragment{ : \hyperref[Ocamlary-Dep11-module-type-S]{\ocamlinlinecode{Dep12(Dep11).\allowbreak{}T}}}\\ +\label{Ocamlary-type-dep5}\ocamlcodefragment{\ocamltag{keyword}{type} dep5 = \hyperref[Ocamlary-Dep11-module-type-S-class-c]{\ocamlinlinecode{Dep13.\allowbreak{}c}}}\\ +\label{Ocamlary-module-type-With1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-With1]{\ocamlinlinecode{With1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With1-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-With1-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With1-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-With1-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[module-Ocamlary-module-type-With1-module-M-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\ +\label{Ocamlary-module-type-With1-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[Ocamlary-module-type-With1-M-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With2-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-With2-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With2-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-With2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With2]{\ocamlinlinecode{With2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With2-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-With2-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With2-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With3]{\ocamlinlinecode{With3}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-type-With1]{\ocamlinlinecode{With1}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-With1-module-M]{\ocamlinlinecode{M}} = \hyperref[module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\\ -\label{module-Ocamlary-type-with1}\ocamlcodefragment{\ocamltag{keyword}{type} with1 = \hyperref[module-Ocamlary-module-With3-module-N-type-t]{\ocamlinlinecode{With3.\allowbreak{}N.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-With4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With4]{\ocamlinlinecode{With4}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-type-With1]{\ocamlinlinecode{With1}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-With1-module-M]{\ocamlinlinecode{M}} := \hyperref[module-Ocamlary-module-With2]{\ocamlinlinecode{With2}}}\\ -\label{module-Ocamlary-type-with2}\ocamlcodefragment{\ocamltag{keyword}{type} with2 = \hyperref[module-Ocamlary-module-With4-module-N-type-t]{\ocamlinlinecode{With4.\allowbreak{}N.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-With5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With5]{\ocamlinlinecode{With5}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With5-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-With5-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With5-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-With3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With3]{\ocamlinlinecode{With3}}}\ocamlcodefragment{ : \hyperref[Ocamlary-module-type-With1]{\ocamlinlinecode{With1}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-With1-M]{\ocamlinlinecode{M}} = \hyperref[Ocamlary-With2]{\ocamlinlinecode{With2}}}\\ +\label{Ocamlary-type-with1}\ocamlcodefragment{\ocamltag{keyword}{type} with1 = \hyperref[Ocamlary-With3-N-type-t]{\ocamlinlinecode{With3.\allowbreak{}N.\allowbreak{}t}}}\\ +\label{Ocamlary-module-With4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With4]{\ocamlinlinecode{With4}}}\ocamlcodefragment{ : \hyperref[Ocamlary-module-type-With1]{\ocamlinlinecode{With1}} \ocamltag{keyword}{with} \ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-With1-M]{\ocamlinlinecode{M}} := \hyperref[Ocamlary-With2]{\ocamlinlinecode{With2}}}\\ +\label{Ocamlary-type-with2}\ocamlcodefragment{\ocamltag{keyword}{type} with2 = \hyperref[Ocamlary-With4-N-type-t]{\ocamlinlinecode{With4.\allowbreak{}N.\allowbreak{}t}}}\\ +\label{Ocamlary-module-With5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With5]{\ocamlinlinecode{With5}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With5-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-With5-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With5-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With5-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With5-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[module-Ocamlary-module-With5-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-With5-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With5-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \hyperref[Ocamlary-With5-module-type-S]{\ocamlinlinecode{S}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With6}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With6]{\ocamlinlinecode{With6}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With6-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-With6-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With6-module-type-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With6-module-type-T-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With6-module-type-T-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ -\label{module-Ocamlary-module-With6-module-type-T-module-M-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[module-Ocamlary-module-With6-module-type-T-module-M-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{Ocamlary-module-With6}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With6]{\ocamlinlinecode{With6}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With6-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-With6-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With6-module-type-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With6-module-type-T-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With6-module-type-T-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ +\label{Ocamlary-With6-module-type-T-M-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[Ocamlary-With6-module-type-T-M-module-type-S]{\ocamlinlinecode{S}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With7}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With7]{\ocamlinlinecode{With7}}}\ocamlcodefragment{ (\hyperref[module-Ocamlary-module-With7-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-With8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-With8]{\ocamlinlinecode{With8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With8-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-With8-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With8-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S = \hyperref[module-Ocamlary-module-With5-module-type-S]{\ocamlinlinecode{With5.\allowbreak{}S}}}\\ -\label{module-Ocamlary-module-type-With8-module-M-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-With8-module-M-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With8-module-M-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[module-Ocamlary-module-With5-module-N-type-t]{\ocamlinlinecode{With5.\allowbreak{}N.\allowbreak{}t}}}\\ +\label{Ocamlary-module-With7}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With7]{\ocamlinlinecode{With7}}}\ocamlcodefragment{ (\hyperref[Ocamlary-With7-argument-1-X]{\ocamlinlinecode{X}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-module-type-With8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-With8]{\ocamlinlinecode{With8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With8-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-With8-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With8-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S = \hyperref[Ocamlary-With5-module-type-S]{\ocamlinlinecode{With5.\allowbreak{}S}}}\\ +\label{Ocamlary-module-type-With8-M-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-With8-M-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With8-M-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[Ocamlary-With5-N-type-t]{\ocamlinlinecode{With5.\allowbreak{}N.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With9}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With9]{\ocamlinlinecode{With9}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With9-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-With9-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With9-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-With9}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With9]{\ocamlinlinecode{With9}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With9-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-With9-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With9-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With10}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With10]{\ocamlinlinecode{With10}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With10-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-With10-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With10-module-type-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-With10-module-type-T-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-With10-module-type-T-module-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ +\label{Ocamlary-module-With10}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With10]{\ocamlinlinecode{With10}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With10-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-With10-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With10-module-type-T-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-With10-module-type-T-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-With10-module-type-T-M-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-With10-module-type-T-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[module-Ocamlary-module-With10-module-type-T-module-M-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\ +\label{Ocamlary-With10-module-type-T-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} N : \hyperref[Ocamlary-With10-module-type-T-M-module-type-S]{\ocamlinlinecode{M.\allowbreak{}S}}}\\ \end{ocamlindent}% -\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}\hyperref[module-Ocamlary-module-With10-module-type-T]{\ocamlinlinecode{\ocamlinlinecode{With10.\allowbreak{}T}}[p\pageref*{module-Ocamlary-module-With10-module-type-T}]} is a submodule type.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}\hyperref[Ocamlary-With10-module-type-T]{\ocamlinlinecode{\ocamlinlinecode{With10.\allowbreak{}T}}[p\pageref*{Ocamlary-With10-module-type-T}]} is a submodule type.\end{ocamlindent}% \medbreak \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-With11}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-With11]{\ocamlinlinecode{With11}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With11-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[module-Ocamlary-module-With9]{\ocamlinlinecode{With9}}}\\ -\label{module-Ocamlary-module-type-With11-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-With11-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-With11-module-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ +\label{Ocamlary-module-type-With11}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-With11]{\ocamlinlinecode{With11}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With11-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[Ocamlary-With9]{\ocamlinlinecode{With9}}}\\ +\label{Ocamlary-module-type-With11-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-module-type-With11-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-With11-N-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-type-NestedInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-NestedInclude1]{\ocamlinlinecode{NestedInclude1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2-type-nested_include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include}\\ +\label{Ocamlary-module-type-NestedInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-NestedInclude1]{\ocamlinlinecode{NestedInclude1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2-type-nested_include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-NestedInclude1]{\ocamlinlinecode{NestedInclude1}}\label{module-Ocamlary-module-type-NestedInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-NestedInclude2-type-nested_include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include}\\ +\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-NestedInclude1]{\ocamlinlinecode{NestedInclude1}}\label{Ocamlary-module-type-NestedInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-NestedInclude2-type-nested_include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-NestedInclude2-type-nested_include]{\ocamlinlinecode{nested\_\allowbreak{}include}} = int\label{module-Ocamlary-type-nested_include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include = int}\\ -\label{module-Ocamlary-module-DoubleInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-DoubleInclude1]{\ocamlinlinecode{DoubleInclude1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-DoubleInclude1-module-DoubleInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-DoubleInclude1-module-DoubleInclude2]{\ocamlinlinecode{DoubleInclude2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-DoubleInclude1-module-DoubleInclude2-type-double_include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\ +\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-NestedInclude2]{\ocamlinlinecode{NestedInclude2}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-NestedInclude2-type-nested_include]{\ocamlinlinecode{nested\_\allowbreak{}include}} = int\label{Ocamlary-type-nested_include}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}include = int}\\ +\label{Ocamlary-module-DoubleInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-DoubleInclude1]{\ocamlinlinecode{DoubleInclude1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-DoubleInclude1-module-DoubleInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-DoubleInclude1-DoubleInclude2]{\ocamlinlinecode{DoubleInclude2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-DoubleInclude1-DoubleInclude2-type-double_include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-DoubleInclude3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-DoubleInclude3]{\ocamlinlinecode{DoubleInclude3}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-DoubleInclude1]{\ocamlinlinecode{DoubleInclude1}}\label{module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2]{\ocamlinlinecode{DoubleInclude2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2-type-double_include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\ +\label{Ocamlary-module-DoubleInclude3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-DoubleInclude3]{\ocamlinlinecode{DoubleInclude3}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-DoubleInclude1]{\ocamlinlinecode{DoubleInclude1}}\label{Ocamlary-DoubleInclude3-module-DoubleInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-DoubleInclude3-DoubleInclude2]{\ocamlinlinecode{DoubleInclude2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-DoubleInclude3-DoubleInclude2-type-double_include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-DoubleInclude3-module-DoubleInclude2]{\ocamlinlinecode{DoubleInclude3.\allowbreak{}DoubleInclude2}}\label{module-Ocamlary-type-double_include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\ -\label{module-Ocamlary-module-IncludeInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-IncludeInclude1]{\ocamlinlinecode{IncludeInclude1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-IncludeInclude1-module-type-IncludeInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-IncludeInclude1-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-IncludeInclude1-module-type-IncludeInclude2-type-include_include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\ +\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-DoubleInclude3-DoubleInclude2]{\ocamlinlinecode{DoubleInclude3.\allowbreak{}DoubleInclude2}}\label{Ocamlary-type-double_include}\ocamlcodefragment{\ocamltag{keyword}{type} double\_\allowbreak{}include}\\ +\label{Ocamlary-module-IncludeInclude1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-IncludeInclude1]{\ocamlinlinecode{IncludeInclude1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-IncludeInclude1-module-type-IncludeInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-IncludeInclude1-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-IncludeInclude1-module-type-IncludeInclude2-type-include_include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-IncludeInclude1-module-IncludeInclude2_M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-IncludeInclude1-module-IncludeInclude2_M]{\ocamlinlinecode{IncludeInclude2\_\allowbreak{}M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-IncludeInclude1-module-IncludeInclude2_M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-IncludeInclude1-IncludeInclude2_M]{\ocamlinlinecode{IncludeInclude2\_\allowbreak{}M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-IncludeInclude1]{\ocamlinlinecode{IncludeInclude1}}\label{module-Ocamlary-module-type-IncludeInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-IncludeInclude2-type-include_include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\ +\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-IncludeInclude1]{\ocamlinlinecode{IncludeInclude1}}\label{Ocamlary-module-type-IncludeInclude2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-IncludeInclude2-type-include_include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-IncludeInclude2_M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-IncludeInclude2_M]{\ocamlinlinecode{IncludeInclude2\_\allowbreak{}M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Ocamlary-module-IncludeInclude2_M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-IncludeInclude2_M]{\ocamlinlinecode{IncludeInclude2\_\allowbreak{}M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\ocamltag{keyword}{include} \hyperref[module-Ocamlary-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}\label{module-Ocamlary-type-include_include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\ +\ocamltag{keyword}{include} \hyperref[Ocamlary-module-type-IncludeInclude2]{\ocamlinlinecode{IncludeInclude2}}\label{Ocamlary-type-include_include}\ocamlcodefragment{\ocamltag{keyword}{type} include\_\allowbreak{}include}\\ \subsection{Trying the \{!modules: ...\} command.\label{indexmodules}}% With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references. @@ -769,130 +769,130 @@ \subsection{Trying the \{!modules: ...\} command.\label{indexmodules}}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{\hyperref[module-Ocamlary-module-Dep1-module-X]{\ocamlinlinecode{\ocamlinlinecode{Dep1.\allowbreak{}X}}[p\pageref*{module-Ocamlary-module-Dep1-module-X}]}}]{}% -\item[{\hyperref[module-Ocamlary-module-IncludeInclude1]{\ocamlinlinecode{\ocamlinlinecode{Ocamlary.\allowbreak{}IncludeInclude1}}[p\pageref*{module-Ocamlary-module-IncludeInclude1}]}}]{}% -\item[{\hyperref[module-Ocamlary]{\ocamlinlinecode{\ocamlinlinecode{Ocamlary}}[p\pageref*{module-Ocamlary}]}}]{This is an \emph{interface} with \bold{all} of the \emph{module system} features. This documentation demonstrates:}\end{description}% +\item[{\hyperref[Ocamlary-Dep1-X]{\ocamlinlinecode{\ocamlinlinecode{Dep1.\allowbreak{}X}}[p\pageref*{Ocamlary-Dep1-X}]}}]{}% +\item[{\hyperref[Ocamlary-IncludeInclude1]{\ocamlinlinecode{\ocamlinlinecode{Ocamlary.\allowbreak{}IncludeInclude1}}[p\pageref*{Ocamlary-IncludeInclude1}]}}]{}% +\item[{\hyperref[Ocamlary]{\ocamlinlinecode{\ocamlinlinecode{Ocamlary}}[p\pageref*{Ocamlary}]}}]{This is an \emph{interface} with \bold{all} of the \emph{module system} features. This documentation demonstrates:}\end{description}% \subsubsection{Weirder usages involving module types\label{weirder-usages-involving-module-types}}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{\hyperref[module-Ocamlary-module-IncludeInclude1-module-IncludeInclude2_M]{\ocamlinlinecode{\ocamlinlinecode{IncludeInclude1.\allowbreak{}IncludeInclude2\_\allowbreak{}M}}[p\pageref*{module-Ocamlary-module-IncludeInclude1-module-IncludeInclude2_M}]}}]{}% -\item[{\hyperref[module-Ocamlary-module-Dep4-module-X]{\ocamlinlinecode{\ocamlinlinecode{Dep4.\allowbreak{}X}}[p\pageref*{module-Ocamlary-module-Dep4-module-X}]}}]{}\end{description}% +\item[{\hyperref[Ocamlary-IncludeInclude1-IncludeInclude2_M]{\ocamlinlinecode{\ocamlinlinecode{IncludeInclude1.\allowbreak{}IncludeInclude2\_\allowbreak{}M}}[p\pageref*{Ocamlary-IncludeInclude1-IncludeInclude2_M}]}}]{}% +\item[{\hyperref[Ocamlary-Dep4-X]{\ocamlinlinecode{\ocamlinlinecode{Dep4.\allowbreak{}X}}[p\pageref*{Ocamlary-Dep4-X}]}}]{}\end{description}% \subsection{Playing with @canonical paths\label{playing-with-@canonical-paths}}% -\label{module-Ocamlary-module-CanonicalTest}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest]{\ocamlinlinecode{CanonicalTest}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CanonicalTest-module-Base}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base]{\ocamlinlinecode{Base}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CanonicalTest-module-Base-module-List}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{List}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-module-CanonicalTest}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CanonicalTest]{\ocamlinlinecode{CanonicalTest}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CanonicalTest-module-Base}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CanonicalTest-Base]{\ocamlinlinecode{Base}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CanonicalTest-Base-module-List}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CanonicalTest-Base-List]{\ocamlinlinecode{List}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-Base_Tests}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base_Tests]{\ocamlinlinecode{Base\_\allowbreak{}Tests}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-CanonicalTest-module-Base_Tests-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base_Tests-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-Base_Tests-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L = \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-Base_Tests-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{L.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} float \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{L.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-Base_Tests-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-Base_Tests-val-baz}\ocamlcodefragment{\ocamltag{keyword}{val} baz : \ocamltag{type-var}{'a} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ +\label{Ocamlary-CanonicalTest-module-Base_Tests}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CanonicalTest-Base_Tests]{\ocamlinlinecode{Base\_\allowbreak{}Tests}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-CanonicalTest-Base_Tests-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CanonicalTest-Base_Tests-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-CanonicalTest-Base-List]{\ocamlinlinecode{Base.\allowbreak{}List}}}\\ +\label{Ocamlary-CanonicalTest-Base_Tests-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L = \hyperref[Ocamlary-CanonicalTest-Base-List]{\ocamlinlinecode{Base.\allowbreak{}List}}}\\ +\label{Ocamlary-CanonicalTest-Base_Tests-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{L.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} float \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{L.\allowbreak{}t}}}\\ +\label{Ocamlary-CanonicalTest-Base_Tests-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : \ocamltag{type-var}{'a} \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} \ocamltag{type-var}{'a} \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\ +\label{Ocamlary-CanonicalTest-Base_Tests-val-baz}\ocamlcodefragment{\ocamltag{keyword}{val} baz : \ocamltag{type-var}{'a} \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-CanonicalTest-module-List_modif}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-CanonicalTest-module-List_modif]{\ocamlinlinecode{List\_\allowbreak{}modif}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{Base.\allowbreak{}List}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} 'c \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{t}} = \ocamltag{type-var}{'c} \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\ +\label{Ocamlary-CanonicalTest-module-List_modif}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-CanonicalTest-List_modif]{\ocamlinlinecode{List\_\allowbreak{}modif}}}\ocamlcodefragment{ : \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-CanonicalTest-Base-List]{\ocamlinlinecode{Base.\allowbreak{}List}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} 'c \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{t}} = \ocamltag{type-var}{'c} \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{Base.\allowbreak{}List.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -Some ref to \hyperref[module-Ocamlary-module-CanonicalTest-module-Base_Tests-module-C-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}C.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base_Tests-module-C-type-t}]} and \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}L.\allowbreak{}id}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-val-id}]}. But also to \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List}]} and \hyperref[module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-CanonicalTest-module-Base-module-List-type-t}]} +Some ref to \hyperref[Ocamlary-CanonicalTest-Base_Tests-C-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}C.\allowbreak{}t}}[p\pageref*{Ocamlary-CanonicalTest-Base_Tests-C-type-t}]} and \hyperref[Ocamlary-CanonicalTest-Base-List-val-id]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base\_\allowbreak{}Tests.\allowbreak{}L.\allowbreak{}id}}[p\pageref*{Ocamlary-CanonicalTest-Base-List-val-id}]}. But also to \hyperref[Ocamlary-CanonicalTest-Base-List]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List}}[p\pageref*{Ocamlary-CanonicalTest-Base-List}]} and \hyperref[Ocamlary-CanonicalTest-Base-List-type-t]{\ocamlinlinecode{\ocamlinlinecode{CanonicalTest.\allowbreak{}Base.\allowbreak{}List.\allowbreak{}t}}[p\pageref*{Ocamlary-CanonicalTest-Base-List-type-t}]} \subsection{Aliases again\label{aliases}}% -\label{module-Ocamlary-module-Aliases}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases]{\ocamlinlinecode{Aliases}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-Foo-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-Foo-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-D]{\ocamlinlinecode{D}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-Foo-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\end{ocamlindent}% -\ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-A'}\ocamlcodefragment{\ocamltag{keyword}{module} A' = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\ -\label{module-Ocamlary-module-Aliases-type-tata}\ocamlcodefragment{\ocamltag{keyword}{type} tata = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{Foo.\allowbreak{}A.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-Aliases-type-tbtb}\ocamlcodefragment{\ocamltag{keyword}{type} tbtb = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-B-type-t]{\ocamlinlinecode{Foo.\allowbreak{}B.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-Aliases-type-tete}\ocamlcodefragment{\ocamltag{keyword}{type} tete}\\ -\label{module-Ocamlary-module-Aliases-type-tata'}\ocamlcodefragment{\ocamltag{keyword}{type} tata' = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{A'.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-Aliases-type-tete2}\ocamlcodefragment{\ocamltag{keyword}{type} tete2 = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-E-type-t]{\ocamlinlinecode{Foo.\allowbreak{}E.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-Aliases-module-Std}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-Std]{\ocamlinlinecode{Std}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-Std-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\ -\label{module-Ocamlary-module-Aliases-module-Std-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ -\label{module-Ocamlary-module-Aliases-module-Std-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-C]{\ocamlinlinecode{Foo.\allowbreak{}C}}}\\ -\label{module-Ocamlary-module-Aliases-module-Std-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-D]{\ocamlinlinecode{Foo.\allowbreak{}D}}}\\ -\label{module-Ocamlary-module-Aliases-module-Std-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} E = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-E]{\ocamlinlinecode{Foo.\allowbreak{}E}}}\\ -\end{ocamlindent}% -\ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-type-stde}\ocamlcodefragment{\ocamltag{keyword}{type} stde = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-E-type-t]{\ocamlinlinecode{Std.\allowbreak{}E.\allowbreak{}t}}}\\ +\label{Ocamlary-module-Aliases}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases]{\ocamlinlinecode{Aliases}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Aliases-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Aliases-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Foo-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Foo-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-Foo-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Foo-C]{\ocamlinlinecode{C}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-Foo-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Foo-D]{\ocamlinlinecode{D}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-Foo-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Foo-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-module-A'}\ocamlcodefragment{\ocamltag{keyword}{module} A' = \hyperref[Ocamlary-Aliases-Foo-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\ +\label{Ocamlary-Aliases-type-tata}\ocamlcodefragment{\ocamltag{keyword}{type} tata = \hyperref[Ocamlary-Aliases-Foo-A-type-t]{\ocamlinlinecode{Foo.\allowbreak{}A.\allowbreak{}t}}}\\ +\label{Ocamlary-Aliases-type-tbtb}\ocamlcodefragment{\ocamltag{keyword}{type} tbtb = \hyperref[Ocamlary-Aliases-Foo-B-type-t]{\ocamlinlinecode{Foo.\allowbreak{}B.\allowbreak{}t}}}\\ +\label{Ocamlary-Aliases-type-tete}\ocamlcodefragment{\ocamltag{keyword}{type} tete}\\ +\label{Ocamlary-Aliases-type-tata'}\ocamlcodefragment{\ocamltag{keyword}{type} tata' = \hyperref[Ocamlary-Aliases-Foo-A-type-t]{\ocamlinlinecode{A'.\allowbreak{}t}}}\\ +\label{Ocamlary-Aliases-type-tete2}\ocamlcodefragment{\ocamltag{keyword}{type} tete2 = \hyperref[Ocamlary-Aliases-Foo-E-type-t]{\ocamlinlinecode{Foo.\allowbreak{}E.\allowbreak{}t}}}\\ +\label{Ocamlary-Aliases-module-Std}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-Std]{\ocamlinlinecode{Std}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Aliases-Std-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[Ocamlary-Aliases-Foo-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\ +\label{Ocamlary-Aliases-Std-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[Ocamlary-Aliases-Foo-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ +\label{Ocamlary-Aliases-Std-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[Ocamlary-Aliases-Foo-C]{\ocamlinlinecode{Foo.\allowbreak{}C}}}\\ +\label{Ocamlary-Aliases-Std-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[Ocamlary-Aliases-Foo-D]{\ocamlinlinecode{Foo.\allowbreak{}D}}}\\ +\label{Ocamlary-Aliases-Std-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} E = \hyperref[Ocamlary-Aliases-Foo-E]{\ocamlinlinecode{Foo.\allowbreak{}E}}}\\ +\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-type-stde}\ocamlcodefragment{\ocamltag{keyword}{type} stde = \hyperref[Ocamlary-Aliases-Foo-E-type-t]{\ocamlinlinecode{Std.\allowbreak{}E.\allowbreak{}t}}}\\ \subsubsection{include of Foo\label{incl}}% -Just for giggle, let's see what happens when we include \hyperref[module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{\ocamlinlinecode{Foo}}[p\pageref*{module-Ocamlary-module-Aliases-module-Foo}]}. +Just for giggle, let's see what happens when we include \hyperref[Ocamlary-Aliases-Foo]{\ocamlinlinecode{\ocamlinlinecode{Foo}}[p\pageref*{Ocamlary-Aliases-Foo}]}. -\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[module-Ocamlary-module-Aliases-module-Foo]{\ocamlinlinecode{Foo}}\label{module-Ocamlary-module-Aliases-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\ -\label{module-Ocamlary-module-Aliases-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ -\label{module-Ocamlary-module-Aliases-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-C]{\ocamlinlinecode{Foo.\allowbreak{}C}}}\\ -\label{module-Ocamlary-module-Aliases-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-D]{\ocamlinlinecode{Foo.\allowbreak{}D}}}\\ -\label{module-Ocamlary-module-Aliases-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-type-testa}\ocamlcodefragment{\ocamltag{keyword}{type} testa = \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{A.\allowbreak{}t}}}\\ -And also, let's refer to \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-A-type-t]{\ocamlinlinecode{\ocamlinlinecode{A.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-Aliases-module-Foo-module-A-type-t}]} and \hyperref[module-Ocamlary-module-Aliases-module-Foo-module-B-val-id]{\ocamlinlinecode{\ocamlinlinecode{Foo.\allowbreak{}B.\allowbreak{}id}}[p\pageref*{module-Ocamlary-module-Aliases-module-Foo-module-B-val-id}]} +\ocamltag{keyword}{include} \ocamltag{keyword}{module} \ocamltag{keyword}{type} \ocamltag{keyword}{of} \hyperref[Ocamlary-Aliases-Foo]{\ocamlinlinecode{Foo}}\label{Ocamlary-Aliases-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} A = \hyperref[Ocamlary-Aliases-Foo-A]{\ocamlinlinecode{Foo.\allowbreak{}A}}}\\ +\label{Ocamlary-Aliases-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} B = \hyperref[Ocamlary-Aliases-Foo-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ +\label{Ocamlary-Aliases-module-C}\ocamlcodefragment{\ocamltag{keyword}{module} C = \hyperref[Ocamlary-Aliases-Foo-C]{\ocamlinlinecode{Foo.\allowbreak{}C}}}\\ +\label{Ocamlary-Aliases-module-D}\ocamlcodefragment{\ocamltag{keyword}{module} D = \hyperref[Ocamlary-Aliases-Foo-D]{\ocamlinlinecode{Foo.\allowbreak{}D}}}\\ +\label{Ocamlary-Aliases-module-E}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-E]{\ocamlinlinecode{E}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-type-testa}\ocamlcodefragment{\ocamltag{keyword}{type} testa = \hyperref[Ocamlary-Aliases-Foo-A-type-t]{\ocamlinlinecode{A.\allowbreak{}t}}}\\ +And also, let's refer to \hyperref[Ocamlary-Aliases-Foo-A-type-t]{\ocamlinlinecode{\ocamlinlinecode{A.\allowbreak{}t}}[p\pageref*{Ocamlary-Aliases-Foo-A-type-t}]} and \hyperref[Ocamlary-Aliases-Foo-B-val-id]{\ocamlinlinecode{\ocamlinlinecode{Foo.\allowbreak{}B.\allowbreak{}id}}[p\pageref*{Ocamlary-Aliases-Foo-B-val-id}]} -\label{module-Ocamlary-module-Aliases-module-P1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-P1]{\ocamlinlinecode{P1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-P1-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-P1-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-P1-module-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Ocamlary-module-Aliases-module-P1-module-Y-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[module-Ocamlary-module-Aliases-module-P1-module-Y-type-t]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[module-Ocamlary-module-Aliases-module-P1-module-Y-type-t]{\ocamlinlinecode{t}}}\\ +\label{Ocamlary-Aliases-module-P1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-P1]{\ocamlinlinecode{P1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Aliases-P1-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-P1-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Aliases-P1-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-Aliases-P1-Y-val-id}\ocamlcodefragment{\ocamltag{keyword}{val} id : \hyperref[Ocamlary-Aliases-P1-Y-type-t]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} \hyperref[Ocamlary-Aliases-P1-Y-type-t]{\ocamlinlinecode{t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-P2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-P2]{\ocamlinlinecode{P2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Aliases-module-P2-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Aliases-module-P2-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Ocamlary-Aliases-module-P2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-P2]{\ocamlinlinecode{P2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Aliases-P2-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Aliases-P2-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Aliases-module-X1}\ocamlcodefragment{\ocamltag{keyword}{module} X1 = \hyperref[module-Ocamlary-module-Aliases-module-P2-module-Z]{\ocamlinlinecode{P2.\allowbreak{}Z}}}\\ -\label{module-Ocamlary-module-Aliases-module-X2}\ocamlcodefragment{\ocamltag{keyword}{module} X2 = \hyperref[module-Ocamlary-module-Aliases-module-P2-module-Z]{\ocamlinlinecode{P2.\allowbreak{}Z}}}\\ -\label{module-Ocamlary-module-Aliases-type-p1}\ocamlcodefragment{\ocamltag{keyword}{type} p1 = \hyperref[module-Ocamlary-module-Aliases-module-P2-module-Z-type-t]{\ocamlinlinecode{X1.\allowbreak{}t}}}\\ -\label{module-Ocamlary-module-Aliases-type-p2}\ocamlcodefragment{\ocamltag{keyword}{type} p2 = \hyperref[module-Ocamlary-module-Aliases-module-P2-module-Z-type-t]{\ocamlinlinecode{X2.\allowbreak{}t}}}\\ +\label{Ocamlary-Aliases-module-X1}\ocamlcodefragment{\ocamltag{keyword}{module} X1 = \hyperref[Ocamlary-Aliases-P2-Z]{\ocamlinlinecode{P2.\allowbreak{}Z}}}\\ +\label{Ocamlary-Aliases-module-X2}\ocamlcodefragment{\ocamltag{keyword}{module} X2 = \hyperref[Ocamlary-Aliases-P2-Z]{\ocamlinlinecode{P2.\allowbreak{}Z}}}\\ +\label{Ocamlary-Aliases-type-p1}\ocamlcodefragment{\ocamltag{keyword}{type} p1 = \hyperref[Ocamlary-Aliases-P2-Z-type-t]{\ocamlinlinecode{X1.\allowbreak{}t}}}\\ +\label{Ocamlary-Aliases-type-p2}\ocamlcodefragment{\ocamltag{keyword}{type} p2 = \hyperref[Ocamlary-Aliases-P2-Z-type-t]{\ocamlinlinecode{X2.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Let's imitate jst's layout.\end{ocamlindent}% \medbreak \subsection{Section title splicing\label{section-title-splicing}}% I can refer to -\begin{itemize}\item{\ocamlinlinecode{\{!section:indexmodules\}} : \hyperref[module-Ocamlary-indexmodules]{\ocamlinlinecode{Trying the \{!modules: ...\} command.}[p\pageref*{module-Ocamlary-indexmodules}]}}% -\item{\ocamlinlinecode{\{!aliases\}} : \hyperref[module-Ocamlary-aliases]{\ocamlinlinecode{Aliases again}[p\pageref*{module-Ocamlary-aliases}]}}\end{itemize}% +\begin{itemize}\item{\ocamlinlinecode{\{!section:indexmodules\}} : \hyperref[Ocamlary-indexmodules]{\ocamlinlinecode{Trying the \{!modules: ...\} command.}[p\pageref*{Ocamlary-indexmodules}]}}% +\item{\ocamlinlinecode{\{!aliases\}} : \hyperref[Ocamlary-aliases]{\ocamlinlinecode{Aliases again}[p\pageref*{Ocamlary-aliases}]}}\end{itemize}% But also to things in submodules: -\begin{itemize}\item{\ocamlinlinecode{\{!section:SuperSig.\allowbreak{}SubSigA.\allowbreak{}subSig\}} : \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig]{\ocamlinlinecode{A Labeled Section Header Inside of a Signature}[p\pageref*{module-Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig}]}}% -\item{\ocamlinlinecode{\{!Aliases.\allowbreak{}incl\}} : \hyperref[module-Ocamlary-module-Aliases-incl]{\ocamlinlinecode{include of Foo}[p\pageref*{module-Ocamlary-module-Aliases-incl}]}}\end{itemize}% +\begin{itemize}\item{\ocamlinlinecode{\{!section:SuperSig.\allowbreak{}SubSigA.\allowbreak{}subSig\}} : \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig]{\ocamlinlinecode{A Labeled Section Header Inside of a Signature}[p\pageref*{Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig}]}}% +\item{\ocamlinlinecode{\{!Aliases.\allowbreak{}incl\}} : \hyperref[Ocamlary-Aliases-incl]{\ocamlinlinecode{include of Foo}[p\pageref*{Ocamlary-Aliases-incl}]}}\end{itemize}% And just to make sure we do not mess up: -\begin{itemize}\item{\ocamlinlinecode{\{\{!section:indexmodules\}A\}} : \hyperref[module-Ocamlary-indexmodules]{\ocamlinlinecode{A}[p\pageref*{module-Ocamlary-indexmodules}]}}% -\item{\ocamlinlinecode{\{\{!aliases\}B\}} : \hyperref[module-Ocamlary-aliases]{\ocamlinlinecode{B}[p\pageref*{module-Ocamlary-aliases}]}}% -\item{\ocamlinlinecode{\{\{!section:SuperSig.\allowbreak{}SubSigA.\allowbreak{}subSig\}C\}} : \hyperref[module-Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig]{\ocamlinlinecode{C}[p\pageref*{module-Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig}]}}% -\item{\ocamlinlinecode{\{\{!Aliases.\allowbreak{}incl\}D\}} : \hyperref[module-Ocamlary-module-Aliases-incl]{\ocamlinlinecode{D}[p\pageref*{module-Ocamlary-module-Aliases-incl}]}}\end{itemize}% +\begin{itemize}\item{\ocamlinlinecode{\{\{!section:indexmodules\}A\}} : \hyperref[Ocamlary-indexmodules]{\ocamlinlinecode{A}[p\pageref*{Ocamlary-indexmodules}]}}% +\item{\ocamlinlinecode{\{\{!aliases\}B\}} : \hyperref[Ocamlary-aliases]{\ocamlinlinecode{B}[p\pageref*{Ocamlary-aliases}]}}% +\item{\ocamlinlinecode{\{\{!section:SuperSig.\allowbreak{}SubSigA.\allowbreak{}subSig\}C\}} : \hyperref[Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig]{\ocamlinlinecode{C}[p\pageref*{Ocamlary-module-type-SuperSig-module-type-SubSigA-subSig}]}}% +\item{\ocamlinlinecode{\{\{!Aliases.\allowbreak{}incl\}D\}} : \hyperref[Ocamlary-Aliases-incl]{\ocamlinlinecode{D}[p\pageref*{Ocamlary-Aliases-incl}]}}\end{itemize}% \subsection{New reference syntax\label{new-reference-syntax}}% -\label{module-Ocamlary-module-type-M}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-type-M}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Ocamlary-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ Here goes: -\begin{itemize}\item{\ocamlinlinecode{\{!module-M.\allowbreak{}t\}} : \hyperref[module-Ocamlary-module-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-M-type-t}]}}% -\item{\ocamlinlinecode{\{!module-type-M.\allowbreak{}t\}} : \hyperref[module-Ocamlary-module-type-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-type-M-type-t}]}}\end{itemize}% -\label{module-Ocamlary-module-Only_a_module}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Only_a_module]{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Only_a_module-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\end{ocamlindent}% -\ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\begin{itemize}\item{\ocamlinlinecode{\{!Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[module-Ocamlary-module-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-Only_a_module-type-t}]}}% -\item{\ocamlinlinecode{\{!module-Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[module-Ocamlary-module-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-Only_a_module-type-t}]}}% -\item{\ocamlinlinecode{\{!module-Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}type-t\}} : \hyperref[module-Ocamlary-module-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-Only_a_module-type-t}]}}% -\item{\ocamlinlinecode{\{!type:Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[module-Ocamlary-module-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{module-Ocamlary-module-Only_a_module-type-t}]}}\end{itemize}% -\label{module-Ocamlary-module-type-TypeExt}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-TypeExt]{\ocamlinlinecode{TypeExt}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-TypeExt-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = .\allowbreak{}.\allowbreak{}}\\ -\label{module-Ocamlary-module-type-TypeExt-extension-decl-C}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-TypeExt-type-t]{\ocamlinlinecode{t}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{module-Ocamlary-module-type-TypeExt-extension-C}\\ +\begin{itemize}\item{\ocamlinlinecode{\{!module-M.\allowbreak{}t\}} : \hyperref[Ocamlary-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{Ocamlary-M-type-t}]}}% +\item{\ocamlinlinecode{\{!module-type-M.\allowbreak{}t\}} : \hyperref[Ocamlary-module-type-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{Ocamlary-module-type-M-type-t}]}}\end{itemize}% +\label{Ocamlary-module-Only_a_module}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Ocamlary-Only_a_module]{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-Only_a_module-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\begin{itemize}\item{\ocamlinlinecode{\{!Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[Ocamlary-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{Ocamlary-Only_a_module-type-t}]}}% +\item{\ocamlinlinecode{\{!module-Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[Ocamlary-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{Ocamlary-Only_a_module-type-t}]}}% +\item{\ocamlinlinecode{\{!module-Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}type-t\}} : \hyperref[Ocamlary-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{Ocamlary-Only_a_module-type-t}]}}% +\item{\ocamlinlinecode{\{!type:Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t\}} : \hyperref[Ocamlary-Only_a_module-type-t]{\ocamlinlinecode{\ocamlinlinecode{Only\_\allowbreak{}a\_\allowbreak{}module.\allowbreak{}t}}[p\pageref*{Ocamlary-Only_a_module-type-t}]}}\end{itemize}% +\label{Ocamlary-module-type-TypeExt}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-TypeExt]{\ocamlinlinecode{TypeExt}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-TypeExt-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = .\allowbreak{}.\allowbreak{}}\\ +\label{Ocamlary-module-type-TypeExt-extension-decl-C}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-TypeExt-type-t]{\ocamlinlinecode{t}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{Ocamlary-module-type-TypeExt-extension-C}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-module-type-TypeExt-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[module-Ocamlary-module-type-TypeExt-type-t]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ +\label{Ocamlary-module-type-TypeExt-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[Ocamlary-module-type-TypeExt-type-t]{\ocamlinlinecode{t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-type-new_t}\ocamlcodefragment{\ocamltag{keyword}{type} new\_\allowbreak{}t = .\allowbreak{}.\allowbreak{}}\\ -\label{module-Ocamlary-extension-decl-C}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-new_t]{\ocamlinlinecode{new\_\allowbreak{}t}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{module-Ocamlary-extension-C}\\ +\label{Ocamlary-type-new_t}\ocamlcodefragment{\ocamltag{keyword}{type} new\_\allowbreak{}t = .\allowbreak{}.\allowbreak{}}\\ +\label{Ocamlary-extension-decl-C}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-new_t]{\ocamlinlinecode{new\_\allowbreak{}t}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{Ocamlary-extension-C}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-module-type-TypeExtPruned}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-TypeExtPruned]{\ocamlinlinecode{TypeExtPruned}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-TypeExtPruned-extension-decl-C}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Ocamlary-type-new_t]{\ocamlinlinecode{new\_\allowbreak{}t}} += }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{module-Ocamlary-module-type-TypeExtPruned-extension-C}\\ +\label{Ocamlary-module-type-TypeExtPruned}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Ocamlary-module-type-TypeExtPruned]{\ocamlinlinecode{TypeExtPruned}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Ocamlary-module-type-TypeExtPruned-extension-decl-C}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Ocamlary-type-new_t]{\ocamlinlinecode{new\_\allowbreak{}t}} += }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{C}}\label{Ocamlary-module-type-TypeExtPruned-extension-C}\\ \end{ocamltabular}% \\ -\label{module-Ocamlary-module-type-TypeExtPruned-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[module-Ocamlary-type-new_t]{\ocamlinlinecode{new\_\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ +\label{Ocamlary-module-type-TypeExtPruned-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[Ocamlary-type-new_t]{\ocamlinlinecode{new\_\allowbreak{}t}} \ocamltag{arrow}{$\rightarrow$} unit}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Unresolved references\label{unresolved-references}}% diff --git a/test/generators/latex/Ocamlary.two_method_class.tex b/test/generators/latex/Ocamlary.two_method_class.tex index a51b9f8926..9e3c1a641f 100644 --- a/test/generators/latex/Ocamlary.two_method_class.tex +++ b/test/generators/latex/Ocamlary.two_method_class.tex @@ -1,5 +1,5 @@ -\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}two\_\allowbreak{}method\_\allowbreak{}class}}\label{module-Ocamlary-class-two_method_class}% -\label{module-Ocamlary-class-two_method_class-method-one}\ocamlcodefragment{\ocamltag{keyword}{method} one : \hyperref[module-Ocamlary-class-one_method_class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\\ -\label{module-Ocamlary-class-two_method_class-method-undo}\ocamlcodefragment{\ocamltag{keyword}{method} undo : unit}\\ +\section{Class \ocamlinlinecode{Ocamlary.\allowbreak{}two\_\allowbreak{}method\_\allowbreak{}class}}\label{Ocamlary-class-two_method_class}% +\label{Ocamlary-class-two_method_class-method-one}\ocamlcodefragment{\ocamltag{keyword}{method} one : \hyperref[Ocamlary-class-one_method_class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\\ +\label{Ocamlary-class-two_method_class-method-undo}\ocamlcodefragment{\ocamltag{keyword}{method} undo : unit}\\ diff --git a/test/generators/latex/Recent.tex b/test/generators/latex/Recent.tex index ef659b96d9..8bab4f170b 100644 --- a/test/generators/latex/Recent.tex +++ b/test/generators/latex/Recent.tex @@ -1,74 +1,74 @@ -\section{Module \ocamlinlinecode{Recent}}\label{module-Recent}% -\label{module-Recent-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Recent-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\section{Module \ocamlinlinecode{Recent}}\label{Recent}% +\label{Recent-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Recent-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Recent-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{module-Recent-module-type-S1-argument-1-_}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent-module-type-S1-argument-1-_]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Recent-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Recent-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{Recent-module-type-S1-argument-1-_}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent-module-type-S1-argument-1-_]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{module-Recent-type-variant.A}% +\label{Recent-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{Recent-type-variant.A}% \begin{ocamlindent}\end{ocamlindent}% -\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{module-Recent-type-variant.B}% +\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{Recent-type-variant.B}% \begin{ocamlindent}\end{ocamlindent}% -\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{module-Recent-type-variant.C}% +\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{Recent-type-variant.C}% \begin{ocamlindent}foo\end{ocamlindent}% -\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{module-Recent-type-variant.D}% +\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{Recent-type-variant.D}% \begin{ocamlindent}\emph{bar}\end{ocamlindent}% \ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{module-Recent-type-variant.a}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{Recent-type-variant.a}\\ \end{ocamltabular}% \\ -\ocamlcodefragment{\}}\label{module-Recent-type-variant.E}% +\ocamlcodefragment{\}}\label{Recent-type-variant.E}% \begin{ocamlindent}\end{ocamlindent}% \end{ocamlindent}% -\label{module-Recent-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{module-Recent-type-gadt.A}% +\label{Recent-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{Recent-type-gadt.A}% \begin{ocamlindent}\end{ocamlindent}% -\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{module-Recent-type-gadt.B}% +\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{Recent-type-gadt.B}% \begin{ocamlindent}foo\end{ocamlindent}% \ocamlcodefragment{| \ocamltag{constructor}{C} : \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{module-Recent-type-gadt.a}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{Recent-type-gadt.a}\\ \end{ocamltabular}% \\ -\ocamlcodefragment{\} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{module-Recent-type-gadt.C}% +\ocamlcodefragment{\} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{Recent-type-gadt.C}% \begin{ocamlindent}\end{ocamlindent}% \end{ocamlindent}% -\label{module-Recent-type-polymorphic_variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| `A}\label{module-Recent-type-polymorphic_variant.A}& \\ -\ocamlcodefragment{| `B \ocamltag{keyword}{of} int}\label{module-Recent-type-polymorphic_variant.B}& \\ -\ocamlcodefragment{| `C}\label{module-Recent-type-polymorphic_variant.C}& foo\\ -\ocamlcodefragment{| `D}\label{module-Recent-type-polymorphic_variant.D}& bar\\ +\label{Recent-type-polymorphic_variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| `A}\label{Recent-type-polymorphic_variant.A}& \\ +\ocamlcodefragment{| `B \ocamltag{keyword}{of} int}\label{Recent-type-polymorphic_variant.B}& \\ +\ocamlcodefragment{| `C}\label{Recent-type-polymorphic_variant.C}& foo\\ +\ocamlcodefragment{| `D}\label{Recent-type-polymorphic_variant.D}& bar\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Recent-type-empty_variant}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}variant = |}\\ -\label{module-Recent-type-nonrec_}\ocamlcodefragment{\ocamltag{keyword}{type} \ocamltag{keyword}{nonrec} nonrec\_\allowbreak{} = int}\\ -\label{module-Recent-type-empty_conj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}conj = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of \& \ocamltag{type-var}{'a} \& int * float ] \ocamltag{arrow}{$\rightarrow$} \hyperref[module-Recent-type-empty_conj]{\ocamlinlinecode{empty\_\allowbreak{}conj}}}\label{module-Recent-type-empty_conj.X}\\ +\label{Recent-type-empty_variant}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}variant = |}\\ +\label{Recent-type-nonrec_}\ocamlcodefragment{\ocamltag{keyword}{type} \ocamltag{keyword}{nonrec} nonrec\_\allowbreak{} = int}\\ +\label{Recent-type-empty_conj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}conj = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of \& \ocamltag{type-var}{'a} \& int * float ] \ocamltag{arrow}{$\rightarrow$} \hyperref[Recent-type-empty_conj]{\ocamlinlinecode{empty\_\allowbreak{}conj}}}\label{Recent-type-empty_conj.X}\\ \end{ocamltabular}% \\ -\label{module-Recent-type-conj}\ocamlcodefragment{\ocamltag{keyword}{type} conj = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of int \& [< `B of int \& float ] ] \ocamltag{arrow}{$\rightarrow$} \hyperref[module-Recent-type-conj]{\ocamlinlinecode{conj}}}\label{module-Recent-type-conj.X}\\ +\label{Recent-type-conj}\ocamlcodefragment{\ocamltag{keyword}{type} conj = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of int \& [< `B of int \& float ] ] \ocamltag{arrow}{$\rightarrow$} \hyperref[Recent-type-conj]{\ocamlinlinecode{conj}}}\label{Recent-type-conj.X}\\ \end{ocamltabular}% \\ -\label{module-Recent-val-empty_conj}\ocamlcodefragment{\ocamltag{keyword}{val} empty\_\allowbreak{}conj : [< `X of \& \ocamltag{type-var}{'a} \& int * float ]}\\ -\label{module-Recent-val-conj}\ocamlcodefragment{\ocamltag{keyword}{val} conj : [< `X of int \& [< `B of int \& float ] ]}\\ -\label{module-Recent-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent-module-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent-module-Z-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent-module-Z-module-Y-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent-module-Z-module-Y-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent-module-Z-module-Y-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} 'a t}\\ +\label{Recent-val-empty_conj}\ocamlcodefragment{\ocamltag{keyword}{val} empty\_\allowbreak{}conj : [< `X of \& \ocamltag{type-var}{'a} \& int * float ]}\\ +\label{Recent-val-conj}\ocamlcodefragment{\ocamltag{keyword}{val} conj : [< `X of int \& [< `B of int \& float ] ]}\\ +\label{Recent-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent-Z-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent-Z-Y-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent-Z-Y-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent-Z-Y-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} 'a t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent-module-X-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L := \hyperref[module-Recent-module-Z-module-Y]{\ocamlinlinecode{Z.\allowbreak{}Y}}}\\ -\label{module-Recent-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int \hyperref[module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{L.\allowbreak{}X.\allowbreak{}t}}}\\ -\label{module-Recent-module-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u := int}\\ -\label{module-Recent-module-X-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \hyperref[module-Recent-module-X-type-u]{\ocamlinlinecode{u}} \hyperref[module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{L.\allowbreak{}X.\allowbreak{}t}}}\\ +\label{Recent-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent-X-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L := \hyperref[Recent-Z-Y]{\ocamlinlinecode{Z.\allowbreak{}Y}}}\\ +\label{Recent-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int \hyperref[Recent-Z-Y-X-type-t]{\ocamlinlinecode{L.\allowbreak{}X.\allowbreak{}t}}}\\ +\label{Recent-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u := int}\\ +\label{Recent-X-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \hyperref[Recent-X-type-u]{\ocamlinlinecode{u}} \hyperref[Recent-Z-Y-X-type-t]{\ocamlinlinecode{L.\allowbreak{}X.\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent-module-type-PolyS}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Recent-module-type-PolyS]{\ocamlinlinecode{PolyS}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent-module-type-PolyS-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A}\label{module-Recent-module-type-PolyS-type-t.A}\\ -\ocamlcodefragment{| `B}\label{module-Recent-module-type-PolyS-type-t.B}\\ +\label{Recent-module-type-PolyS}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Recent-module-type-PolyS]{\ocamlinlinecode{PolyS}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent-module-type-PolyS-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A}\label{Recent-module-type-PolyS-type-t.A}\\ +\ocamlcodefragment{| `B}\label{Recent-module-type-PolyS-type-t.B}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ diff --git a/test/generators/latex/Recent_impl.B.tex b/test/generators/latex/Recent_impl.B.tex index 1dec7d6b71..e9da394fba 100644 --- a/test/generators/latex/Recent_impl.B.tex +++ b/test/generators/latex/Recent_impl.B.tex @@ -1,6 +1,6 @@ -\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl.\allowbreak{}B}}\label{module-Recent_impl-module-B}% -\label{module-Recent_impl-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{module-Recent_impl-module-B-type-t.B}\\ +\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl.\allowbreak{}B}}\label{Recent_impl-B}% +\label{Recent_impl-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{Recent_impl-B-type-t.B}\\ \end{ocamltabular}% \\ diff --git a/test/generators/latex/Recent_impl.tex b/test/generators/latex/Recent_impl.tex index 51c9cee26c..d7bfb7d106 100644 --- a/test/generators/latex/Recent_impl.tex +++ b/test/generators/latex/Recent_impl.tex @@ -1,32 +1,32 @@ -\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl}}\label{module-Recent_impl}% -\label{module-Recent_impl-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent_impl-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent_impl-module-Foo-module-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{module-Recent_impl-module-Foo-module-A-type-t.A}\\ +\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl}}\label{Recent_impl}% +\label{Recent_impl-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent_impl-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-Foo-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent_impl-Foo-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{Recent_impl-Foo-A-type-t.A}\\ \end{ocamltabular}% \\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent_impl-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent_impl-module-Foo-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{module-Recent_impl-module-Foo-module-B-type-t.B}\\ +\label{Recent_impl-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-Foo-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent_impl-Foo-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{Recent_impl-Foo-B-type-t.B}\\ \end{ocamltabular}% \\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent_impl-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Recent_impl-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ -\label{module-Recent_impl-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Recent_impl-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Recent_impl-module-type-S-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-type-S-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{module-Recent_impl-module-type-S-module-F-argument-1-_}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-type-S-module-F-argument-1-_]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Recent_impl-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{Recent_impl-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Recent_impl-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Recent_impl-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Recent_impl-module-type-S-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-module-type-S-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{Recent_impl-module-type-S-F-argument-1-_}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-module-type-S-F-argument-1-_]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% -\label{module-Recent_impl-module-type-S-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Recent_impl-module-type-S-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent_impl-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Recent_impl-module-type-S-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Recent_impl-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Recent_impl-module-type-S-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent_impl-module-type-S-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[module-Recent_impl-module-type-S-module-F-type-t]{\ocamlinlinecode{F(X).\allowbreak{}t}}}\\ +\label{Recent_impl-module-type-S-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[Recent_impl-module-type-S-F-type-t]{\ocamlinlinecode{F(X).\allowbreak{}t}}}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Recent_impl-module-B'}\ocamlcodefragment{\ocamltag{keyword}{module} B' = \hyperref[module-Recent_impl-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ +\label{Recent_impl-module-B'}\ocamlcodefragment{\ocamltag{keyword}{module} B' = \hyperref[Recent_impl-Foo-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ \input{Recent_impl.B.tex} diff --git a/test/generators/latex/Section.tex b/test/generators/latex/Section.tex index ce845e6775..709e5fe4ec 100644 --- a/test/generators/latex/Section.tex +++ b/test/generators/latex/Section.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Section}}\label{module-Section}% +\section{Module \ocamlinlinecode{Section}}\label{Section}% This is the module comment. Eventually, sections won't be allowed in it. \subsection{Empty section\label{empty-section}}% @@ -9,7 +9,7 @@ \subsection{Aside only\label{aside-only}}% Foo bar. \subsection{Value only\label{value-only}}% -\label{module-Section-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ +\label{Section-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsection{Empty section\label{empty-section_2}}% \subsection{within a comment\label{within-a-comment}}% \subsubsection{and one with a nested section\label{and-one-with-a-nested-section}}% diff --git a/test/generators/latex/Stop.tex b/test/generators/latex/Stop.tex index a25cd243e9..73b651767b 100644 --- a/test/generators/latex/Stop.tex +++ b/test/generators/latex/Stop.tex @@ -1,7 +1,7 @@ -\section{Module \ocamlinlinecode{Stop}}\label{module-Stop}% +\section{Module \ocamlinlinecode{Stop}}\label{Stop}% This test cases exercises stop comments. -\label{module-Stop-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\begin{ocamlindent}This is normal commented text.\end{ocamlindent}% +\label{Stop-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\begin{ocamlindent}This is normal commented text.\end{ocamlindent}% \medbreak The next value is \ocamlinlinecode{bar}, and it should be missing from the documentation. There is also an entire module, \ocamlinlinecode{M}, which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. @@ -9,18 +9,18 @@ \section{Module \ocamlinlinecode{Stop}}\label{module-Stop}% Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module. -\label{module-Stop-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Stop-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Stop-module-N-val-quux}\ocamlcodefragment{\ocamltag{keyword}{val} quux : int}\\ +\label{Stop-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Stop-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Stop-N-val-quux}\ocamlcodefragment{\ocamltag{keyword}{val} quux : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Stop-val-lol}\ocamlcodefragment{\ocamltag{keyword}{val} lol : int}\\ -The first comment can also be a stop-comment. The test case \ocamlinlinecode{stop\_\allowbreak{}first\_\allowbreak{}comment.\allowbreak{}mli} is testing the same thing but at the toplevel. We should see \ocamlinlinecode{bar} inside \hyperref[module-Stop-module-O]{\ocamlinlinecode{\ocamlinlinecode{O}}[p\pageref*{module-Stop-module-O}]}. +\label{Stop-val-lol}\ocamlcodefragment{\ocamltag{keyword}{val} lol : int}\\ +The first comment can also be a stop-comment. The test case \ocamlinlinecode{stop\_\allowbreak{}first\_\allowbreak{}comment.\allowbreak{}mli} is testing the same thing but at the toplevel. We should see \ocamlinlinecode{bar} inside \hyperref[Stop-O]{\ocamlinlinecode{\ocamlinlinecode{O}}[p\pageref*{Stop-O}]}. -\label{module-Stop-module-O}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Stop-module-O]{\ocamlinlinecode{O}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Stop-module-O-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : int}\\ +\label{Stop-module-O}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Stop-O]{\ocamlinlinecode{O}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Stop-O-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ The top-comment computation must not mess with stop comments. -\label{module-Stop-module-P}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Stop-module-P]{\ocamlinlinecode{P}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Stop-module-P-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : int}\\ +\label{Stop-module-P}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Stop-P]{\ocamlinlinecode{P}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Stop-P-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/Stop_dead_link_doc.tex b/test/generators/latex/Stop_dead_link_doc.tex index ed43b4f1af..c676e82b64 100644 --- a/test/generators/latex/Stop_dead_link_doc.tex +++ b/test/generators/latex/Stop_dead_link_doc.tex @@ -1,41 +1,41 @@ -\section{Module \ocamlinlinecode{Stop\_\allowbreak{}dead\_\allowbreak{}link\_\allowbreak{}doc}}\label{module-Stop_dead_link_doc}% -\label{module-Stop_dead_link_doc-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Stop_dead_link_doc-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Stop_dead_link_doc-module-Foo-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\section{Module \ocamlinlinecode{Stop\_\allowbreak{}dead\_\allowbreak{}link\_\allowbreak{}doc}}\label{Stop_dead_link_doc}% +\label{Stop_dead_link_doc-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Stop_dead_link_doc-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Stop_dead_link_doc-Foo-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Stop_dead_link_doc-type-foo}\ocamlcodefragment{\ocamltag{keyword}{type} foo = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \hyperref[module-Stop_dead_link_doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}}}\label{module-Stop_dead_link_doc-type-foo.Bar}\\ +\label{Stop_dead_link_doc-type-foo}\ocamlcodefragment{\ocamltag{keyword}{type} foo = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \hyperref[Stop_dead_link_doc-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}}}\label{Stop_dead_link_doc-type-foo.Bar}\\ \end{ocamltabular}% \\ -\label{module-Stop_dead_link_doc-type-bar}\ocamlcodefragment{\ocamltag{keyword}{type} bar = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field : \hyperref[module-Stop_dead_link_doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}};\allowbreak{}}\label{module-Stop_dead_link_doc-type-bar.field}\\ +\label{Stop_dead_link_doc-type-bar}\ocamlcodefragment{\ocamltag{keyword}{type} bar = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \{}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field : \hyperref[Stop_dead_link_doc-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}};\allowbreak{}}\label{Stop_dead_link_doc-type-bar.field}\\ \end{ocamltabular}% \\ -\ocamlcodefragment{\}}\label{module-Stop_dead_link_doc-type-bar.Bar}\\ +\ocamlcodefragment{\}}\label{Stop_dead_link_doc-type-bar.Bar}\\ \end{ocamlindent}% -\label{module-Stop_dead_link_doc-type-foo_}\ocamlcodefragment{\ocamltag{keyword}{type} foo\_\allowbreak{} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}} \ocamltag{keyword}{of} int * \hyperref[module-Stop_dead_link_doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} * int}\label{module-Stop_dead_link_doc-type-foo_.Bar_}\\ +\label{Stop_dead_link_doc-type-foo_}\ocamlcodefragment{\ocamltag{keyword}{type} foo\_\allowbreak{} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}} \ocamltag{keyword}{of} int * \hyperref[Stop_dead_link_doc-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} * int}\label{Stop_dead_link_doc-type-foo_.Bar_}\\ \end{ocamltabular}% \\ -\label{module-Stop_dead_link_doc-type-bar_}\ocamlcodefragment{\ocamltag{keyword}{type} bar\_\allowbreak{} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[module-Stop_dead_link_doc-module-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} option}\label{module-Stop_dead_link_doc-type-bar_.Bar__}\\ +\label{Stop_dead_link_doc-type-bar_}\ocamlcodefragment{\ocamltag{keyword}{type} bar\_\allowbreak{} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[Stop_dead_link_doc-Foo-type-t]{\ocamlinlinecode{Foo.\allowbreak{}t}} option}\label{Stop_dead_link_doc-type-bar_.Bar__}\\ \end{ocamltabular}% \\ -\label{module-Stop_dead_link_doc-type-another_foo}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}}}\label{module-Stop_dead_link_doc-type-another_foo.Bar}\\ +\label{Stop_dead_link_doc-type-another_foo}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}}}\label{Stop_dead_link_doc-type-another_foo.Bar}\\ \end{ocamltabular}% \\ -\label{module-Stop_dead_link_doc-type-another_bar}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field : \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}};\allowbreak{}}\label{module-Stop_dead_link_doc-type-another_bar.field}\\ +\label{Stop_dead_link_doc-type-another_bar}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar = }\begin{ocamlindent}\ocamlcodefragment{| \ocamltag{constructor}{Bar} \ocamltag{keyword}{of} \{}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{field : \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}};\allowbreak{}}\label{Stop_dead_link_doc-type-another_bar.field}\\ \end{ocamltabular}% \\ -\ocamlcodefragment{\}}\label{module-Stop_dead_link_doc-type-another_bar.Bar}\\ +\ocamlcodefragment{\}}\label{Stop_dead_link_doc-type-another_bar.Bar}\\ \end{ocamlindent}% -\label{module-Stop_dead_link_doc-type-another_foo_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo\_\allowbreak{} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}} \ocamltag{keyword}{of} int * \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}} * int}\label{module-Stop_dead_link_doc-type-another_foo_.Bar_}\\ +\label{Stop_dead_link_doc-type-another_foo_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}foo\_\allowbreak{} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}} \ocamltag{keyword}{of} int * \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}} * int}\label{Stop_dead_link_doc-type-another_foo_.Bar_}\\ \end{ocamltabular}% \\ -\label{module-Stop_dead_link_doc-type-another_bar_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar\_\allowbreak{} = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}} option}\label{module-Stop_dead_link_doc-type-another_bar_.Bar__}\\ +\label{Stop_dead_link_doc-type-another_bar_}\ocamlcodefragment{\ocamltag{keyword}{type} another\_\allowbreak{}bar\_\allowbreak{} = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{Bar\_\allowbreak{}\_\allowbreak{}} \ocamltag{keyword}{of} \hyperref[xref-unresolved]{\ocamlinlinecode{Another\_\allowbreak{}Foo.\allowbreak{}t}} option}\label{Stop_dead_link_doc-type-another_bar_.Bar__}\\ \end{ocamltabular}% \\ diff --git a/test/generators/latex/Stop_first_comment.tex b/test/generators/latex/Stop_first_comment.tex index a9334cc9ff..da18d8942f 100644 --- a/test/generators/latex/Stop_first_comment.tex +++ b/test/generators/latex/Stop_first_comment.tex @@ -1,4 +1,4 @@ -\section{Module \ocamlinlinecode{Stop\_\allowbreak{}first\_\allowbreak{}comment}}\label{module-Stop_first_comment}% -\label{module-Stop_first_comment-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : int}\\ +\section{Module \ocamlinlinecode{Stop\_\allowbreak{}first\_\allowbreak{}comment}}\label{Stop_first_comment}% +\label{Stop_first_comment-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : int}\\ diff --git a/test/generators/latex/Tag_link.tex b/test/generators/latex/Tag_link.tex index 8ab0ead292..fd728e5838 100644 --- a/test/generators/latex/Tag_link.tex +++ b/test/generators/latex/Tag_link.tex @@ -1,33 +1,33 @@ -\section{Module \ocamlinlinecode{Tag\_\allowbreak{}link}}\label{module-Tag_link}% -\label{module-Tag_link-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ +\section{Module \ocamlinlinecode{Tag\_\allowbreak{}link}}\label{Tag_link}% +\label{Tag_link-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{deprecated}]{\hyperref[module-Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Tag_link-val-foo}]} +\item[{deprecated}]{\hyperref[Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Tag_link-val-foo}]} }\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{parameter foo}]{\hyperref[module-Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Tag_link-val-foo}]} +\item[{parameter foo}]{\hyperref[Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Tag_link-val-foo}]} }\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{raises \ocamlinlinecode{Foo}}]{\hyperref[module-Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Tag_link-val-foo}]} +\item[{raises \ocamlinlinecode{Foo}}]{\hyperref[Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Tag_link-val-foo}]} }\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{returns}]{\hyperref[module-Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Tag_link-val-foo}]} +\item[{returns}]{\hyperref[Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Tag_link-val-foo}]} }\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{see foo}]{\hyperref[module-Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Tag_link-val-foo}]} +\item[{see foo}]{\hyperref[Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Tag_link-val-foo}]} }\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[{before 0.0.1}]{\hyperref[module-Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{module-Tag_link-val-foo}]} +\item[{before 0.0.1}]{\hyperref[Tag_link-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{Tag_link-val-foo}]} }\end{description}% diff --git a/test/generators/latex/Toplevel_comments.Alias.tex b/test/generators/latex/Toplevel_comments.Alias.tex index 80032de56f..5f540c2d19 100644 --- a/test/generators/latex/Toplevel_comments.Alias.tex +++ b/test/generators/latex/Toplevel_comments.Alias.tex @@ -1,8 +1,8 @@ -\section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}Alias}}\label{module-Toplevel_comments-module-Alias}% +\section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}Alias}}\label{Toplevel_comments-Alias}% Doc of \ocamlinlinecode{Alias}. Doc of \ocamlinlinecode{T}, part 2. -\label{module-Toplevel_comments-module-Alias-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-Alias-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/generators/latex/Toplevel_comments.c1.tex b/test/generators/latex/Toplevel_comments.c1.tex index 2a131f2f81..531102a8a8 100644 --- a/test/generators/latex/Toplevel_comments.c1.tex +++ b/test/generators/latex/Toplevel_comments.c1.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}c1}}\label{module-Toplevel_comments-class-c1}% +\section{Class \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}c1}}\label{Toplevel_comments-class-c1}% Doc of \ocamlinlinecode{c1}, part 1. Doc of \ocamlinlinecode{c1}, part 2. diff --git a/test/generators/latex/Toplevel_comments.c2.tex b/test/generators/latex/Toplevel_comments.c2.tex index d07d19d77e..9ce2ee801a 100644 --- a/test/generators/latex/Toplevel_comments.c2.tex +++ b/test/generators/latex/Toplevel_comments.c2.tex @@ -1,4 +1,4 @@ -\section{Class \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}c2}}\label{module-Toplevel_comments-class-c2}% +\section{Class \ocamlinlinecode{Toplevel\_\allowbreak{}comments.\allowbreak{}c2}}\label{Toplevel_comments-class-c2}% Doc of \ocamlinlinecode{c2}. Doc of \ocamlinlinecode{ct}, part 2. diff --git a/test/generators/latex/Toplevel_comments.tex b/test/generators/latex/Toplevel_comments.tex index 95810bca38..6c9f4a8937 100644 --- a/test/generators/latex/Toplevel_comments.tex +++ b/test/generators/latex/Toplevel_comments.tex @@ -1,53 +1,53 @@ -\section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments}}\label{module-Toplevel_comments}% +\section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments}}\label{Toplevel_comments}% A doc comment at the beginning of a module is considered to be that module's doc. -\label{module-Toplevel_comments-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Toplevel_comments-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-type-T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Toplevel_comments-module-type-T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{T}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-Include_inline}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-Include_inline]{\ocamlinlinecode{Include\_\allowbreak{}inline}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[module-Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{module-Toplevel_comments-module-Include_inline-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-Include_inline}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-Include_inline]{\ocamlinlinecode{Include\_\allowbreak{}inline}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{Toplevel_comments-Include_inline-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{T}, part 2.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-Include_inline'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-Include_inline']{\ocamlinlinecode{Include\_\allowbreak{}inline'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}part 3\ocamltag{keyword}{include} \hyperref[module-Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{module-Toplevel_comments-module-Include_inline'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-Include_inline'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-Include_inline']{\ocamlinlinecode{Include\_\allowbreak{}inline'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}part 3\ocamltag{keyword}{include} \hyperref[Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{Toplevel_comments-Include_inline'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{Include\_\allowbreak{}inline}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-type-Include_inline_T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Toplevel_comments-module-type-Include_inline_T]{\ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[module-Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{module-Toplevel_comments-module-type-Include_inline_T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-type-Include_inline_T}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Toplevel_comments-module-type-Include_inline_T]{\ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\ocamltag{keyword}{include} \hyperref[Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{Toplevel_comments-module-type-Include_inline_T-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{T}, part 2.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-type-Include_inline_T'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Toplevel_comments-module-type-Include_inline_T']{\ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}part 3\ocamltag{keyword}{include} \hyperref[module-Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{module-Toplevel_comments-module-type-Include_inline_T'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-type-Include_inline_T'}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Toplevel_comments-module-type-Include_inline_T']{\ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T'}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}part 3\ocamltag{keyword}{include} \hyperref[Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}\label{Toplevel_comments-module-type-Include_inline_T'-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{Include\_\allowbreak{}inline\_\allowbreak{}T'}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Toplevel_comments-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{M}\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Toplevel_comments-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{M'} from outside\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-M''}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-M'']{\ocamlinlinecode{M''}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\label{Toplevel_comments-module-M''}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-M'']{\ocamlinlinecode{M''}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{M''}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-Alias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-Alias]{\ocamlinlinecode{Alias}}}\ocamlcodefragment{ : \hyperref[module-Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}}\begin{ocamlindent}Doc of \ocamlinlinecode{Alias}.\end{ocamlindent}% +\label{Toplevel_comments-module-Alias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-Alias]{\ocamlinlinecode{Alias}}}\ocamlcodefragment{ : \hyperref[Toplevel_comments-module-type-T]{\ocamlinlinecode{T}}}\begin{ocamlindent}Doc of \ocamlinlinecode{Alias}.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-class-c1}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Toplevel_comments-class-c1]{\ocamlinlinecode{c1}}}\ocamlcodefragment{ : int \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{c1}, part 1.\end{ocamlindent}% +\label{Toplevel_comments-class-c1}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Toplevel_comments-class-c1]{\ocamlinlinecode{c1}}}\ocamlcodefragment{ : int \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{c1}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-class-type-ct}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Toplevel_comments-class-type-ct]{\ocamlinlinecode{ct}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{Toplevel_comments-class-type-ct}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[Toplevel_comments-class-type-ct]{\ocamlinlinecode{ct}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{ct}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-class-c2}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Toplevel_comments-class-c2]{\ocamlinlinecode{c2}}}\ocamlcodefragment{ : \hyperref[module-Toplevel_comments-class-type-ct]{\ocamlinlinecode{ct}}}\begin{ocamlindent}Doc of \ocamlinlinecode{c2}.\end{ocamlindent}% +\label{Toplevel_comments-class-c2}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[Toplevel_comments-class-c2]{\ocamlinlinecode{c2}}}\ocamlcodefragment{ : \hyperref[Toplevel_comments-class-type-ct]{\ocamlinlinecode{ct}}}\begin{ocamlindent}Doc of \ocamlinlinecode{c2}.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-Ref_in_synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-Ref_in_synopsis]{\ocamlinlinecode{Ref\_\allowbreak{}in\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Toplevel_comments-module-Ref_in_synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-Ref_in_synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-Ref_in_synopsis]{\ocamlinlinecode{Ref\_\allowbreak{}in\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Toplevel_comments-Ref_in_synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}\hyperref[module-Toplevel_comments-module-Ref_in_synopsis-type-t]{\ocamlinlinecode{\ocamlinlinecode{t}}[p\pageref*{module-Toplevel_comments-module-Ref_in_synopsis-type-t}]}.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}\hyperref[Toplevel_comments-Ref_in_synopsis-type-t]{\ocamlinlinecode{\ocamlinlinecode{t}}[p\pageref*{Toplevel_comments-Ref_in_synopsis-type-t}]}.\end{ocamlindent}% \medbreak -\label{module-Toplevel_comments-module-Comments_on_open}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-Comments_on_open]{\ocamlinlinecode{Comments\_\allowbreak{}on\_\allowbreak{}open}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Toplevel_comments-module-Comments_on_open-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel_comments-module-Comments_on_open-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Toplevel_comments-module-Comments_on_open-module-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Toplevel_comments-module-Comments_on_open}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-Comments_on_open]{\ocamlinlinecode{Comments\_\allowbreak{}on\_\allowbreak{}open}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Toplevel_comments-Comments_on_open-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[Toplevel_comments-Comments_on_open-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Toplevel_comments-Comments_on_open-M-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Section\label{sec}}% -Comments attached to open are treated as floating comments. Referencing \hyperref[module-Toplevel_comments-module-Comments_on_open-sec]{\ocamlinlinecode{Section}[p\pageref*{module-Toplevel_comments-module-Comments_on_open-sec}]} \hyperref[module-Toplevel_comments-module-Comments_on_open-module-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{module-Toplevel_comments-module-Comments_on_open-module-M-type-t}]} works +Comments attached to open are treated as floating comments. Referencing \hyperref[Toplevel_comments-Comments_on_open-sec]{\ocamlinlinecode{Section}[p\pageref*{Toplevel_comments-Comments_on_open-sec}]} \hyperref[Toplevel_comments-Comments_on_open-M-type-t]{\ocamlinlinecode{\ocamlinlinecode{M.\allowbreak{}t}}[p\pageref*{Toplevel_comments-Comments_on_open-M-type-t}]} works \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/generators/latex/Type.tex b/test/generators/latex/Type.tex index 3c4fa57092..2ad9aa49da 100644 --- a/test/generators/latex/Type.tex +++ b/test/generators/latex/Type.tex @@ -1,134 +1,134 @@ -\section{Module \ocamlinlinecode{Type}}\label{module-Type}% -\label{module-Type-type-abstract}\ocamlcodefragment{\ocamltag{keyword}{type} abstract}\begin{ocamlindent}Some \emph{documentation}.\end{ocamlindent}% +\section{Module \ocamlinlinecode{Type}}\label{Type}% +\label{Type-type-abstract}\ocamlcodefragment{\ocamltag{keyword}{type} abstract}\begin{ocamlindent}Some \emph{documentation}.\end{ocamlindent}% \medbreak -\label{module-Type-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = int}\\ -\label{module-Type-type-private_}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{} = \ocamltag{keyword}{private} int}\\ -\label{module-Type-type-constructor}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constructor = \ocamltag{type-var}{'a}}\\ -\label{module-Type-type-arrow}\ocamlcodefragment{\ocamltag{keyword}{type} arrow = int \ocamltag{arrow}{$\rightarrow$} int}\\ -\label{module-Type-type-higher_order}\ocamlcodefragment{\ocamltag{keyword}{type} higher\_\allowbreak{}order = (int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\ -\label{module-Type-type-labeled}\ocamlcodefragment{\ocamltag{keyword}{type} labeled = \ocamltag{label}{l}:int \ocamltag{arrow}{$\rightarrow$} int}\\ -\label{module-Type-type-optional}\ocamlcodefragment{\ocamltag{keyword}{type} optional = \ocamltag{optlabel}{?l}:int \ocamltag{arrow}{$\rightarrow$} int}\\ -\label{module-Type-type-labeled_higher_order}\ocamlcodefragment{\ocamltag{keyword}{type} labeled\_\allowbreak{}higher\_\allowbreak{}order = (\ocamltag{label}{l}:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (\ocamltag{optlabel}{?l}:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\ -\label{module-Type-type-pair}\ocamlcodefragment{\ocamltag{keyword}{type} pair = int * int}\\ -\label{module-Type-type-parens_dropped}\ocamlcodefragment{\ocamltag{keyword}{type} parens\_\allowbreak{}dropped = int * int}\\ -\label{module-Type-type-triple}\ocamlcodefragment{\ocamltag{keyword}{type} triple = int * int * int}\\ -\label{module-Type-type-nested_pair}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}pair = (int * int) * int}\\ -\label{module-Type-type-instance}\ocamlcodefragment{\ocamltag{keyword}{type} instance = int \hyperref[module-Type-type-constructor]{\ocamlinlinecode{constructor}}}\\ -\label{module-Type-type-long}\ocamlcodefragment{\ocamltag{keyword}{type} long = - \hyperref[module-Type-type-labeled_higher_order]{\ocamlinlinecode{labeled\_\allowbreak{}higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} - [ `Bar | `Baz of \hyperref[module-Type-type-triple]{\ocamlinlinecode{triple}} ] \ocamltag{arrow}{$\rightarrow$} - \hyperref[module-Type-type-pair]{\ocamlinlinecode{pair}} \ocamltag{arrow}{$\rightarrow$} - \hyperref[module-Type-type-labeled]{\ocamlinlinecode{labeled}} \ocamltag{arrow}{$\rightarrow$} - \hyperref[module-Type-type-higher_order]{\ocamlinlinecode{higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} +\label{Type-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = int}\\ +\label{Type-type-private_}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{} = \ocamltag{keyword}{private} int}\\ +\label{Type-type-constructor}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constructor = \ocamltag{type-var}{'a}}\\ +\label{Type-type-arrow}\ocamlcodefragment{\ocamltag{keyword}{type} arrow = int \ocamltag{arrow}{$\rightarrow$} int}\\ +\label{Type-type-higher_order}\ocamlcodefragment{\ocamltag{keyword}{type} higher\_\allowbreak{}order = (int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\ +\label{Type-type-labeled}\ocamlcodefragment{\ocamltag{keyword}{type} labeled = \ocamltag{label}{l}:int \ocamltag{arrow}{$\rightarrow$} int}\\ +\label{Type-type-optional}\ocamlcodefragment{\ocamltag{keyword}{type} optional = \ocamltag{optlabel}{?l}:int \ocamltag{arrow}{$\rightarrow$} int}\\ +\label{Type-type-labeled_higher_order}\ocamlcodefragment{\ocamltag{keyword}{type} labeled\_\allowbreak{}higher\_\allowbreak{}order = (\ocamltag{label}{l}:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (\ocamltag{optlabel}{?l}:int \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} int}\\ +\label{Type-type-pair}\ocamlcodefragment{\ocamltag{keyword}{type} pair = int * int}\\ +\label{Type-type-parens_dropped}\ocamlcodefragment{\ocamltag{keyword}{type} parens\_\allowbreak{}dropped = int * int}\\ +\label{Type-type-triple}\ocamlcodefragment{\ocamltag{keyword}{type} triple = int * int * int}\\ +\label{Type-type-nested_pair}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}pair = (int * int) * int}\\ +\label{Type-type-instance}\ocamlcodefragment{\ocamltag{keyword}{type} instance = int \hyperref[Type-type-constructor]{\ocamlinlinecode{constructor}}}\\ +\label{Type-type-long}\ocamlcodefragment{\ocamltag{keyword}{type} long = + \hyperref[Type-type-labeled_higher_order]{\ocamlinlinecode{labeled\_\allowbreak{}higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} + [ `Bar | `Baz of \hyperref[Type-type-triple]{\ocamlinlinecode{triple}} ] \ocamltag{arrow}{$\rightarrow$} + \hyperref[Type-type-pair]{\ocamlinlinecode{pair}} \ocamltag{arrow}{$\rightarrow$} + \hyperref[Type-type-labeled]{\ocamlinlinecode{labeled}} \ocamltag{arrow}{$\rightarrow$} + \hyperref[Type-type-higher_order]{\ocamlinlinecode{higher\_\allowbreak{}order}} \ocamltag{arrow}{$\rightarrow$} (string \ocamltag{arrow}{$\rightarrow$} int) \ocamltag{arrow}{$\rightarrow$} (int * float * char * string * char * unit) option \ocamltag{arrow}{$\rightarrow$} - \hyperref[module-Type-type-nested_pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} \ocamltag{arrow}{$\rightarrow$} - \hyperref[module-Type-type-arrow]{\ocamlinlinecode{arrow}} \ocamltag{arrow}{$\rightarrow$} + \hyperref[Type-type-nested_pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} \ocamltag{arrow}{$\rightarrow$} + \hyperref[Type-type-arrow]{\ocamlinlinecode{arrow}} \ocamltag{arrow}{$\rightarrow$} string \ocamltag{arrow}{$\rightarrow$} - \hyperref[module-Type-type-nested_pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} array}\\ -\label{module-Type-type-variant_e}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}e = \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{module-Type-type-variant_e.a}\\ + \hyperref[Type-type-nested_pair]{\ocamlinlinecode{nested\_\allowbreak{}pair}} array}\\ +\label{Type-type-variant_e}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}e = \{}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{Type-type-variant_e.a}\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\\ -\label{module-Type-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{module-Type-type-variant.A}& \\ -\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{module-Type-type-variant.B}& \\ -\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{module-Type-type-variant.C}& foo\\ -\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{module-Type-type-variant.D}& \emph{bar}\\ -\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \hyperref[module-Type-type-variant_e]{\ocamlinlinecode{variant\_\allowbreak{}e}}}\label{module-Type-type-variant.E}& \\ +\label{Type-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{Type-type-variant.A}& \\ +\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{Type-type-variant.B}& \\ +\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{Type-type-variant.C}& foo\\ +\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{Type-type-variant.D}& \emph{bar}\\ +\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \hyperref[Type-type-variant_e]{\ocamlinlinecode{variant\_\allowbreak{}e}}}\label{Type-type-variant.E}& \\ \end{ocamltabular}% \\ -\label{module-Type-type-variant_c}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}c = \{}\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{module-Type-type-variant_c.a}\\ +\label{Type-type-variant_c}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}c = \{}\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{Type-type-variant_c.a}\\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\\ -\label{module-Type-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{module-Type-type-gadt.A}\\ -\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{module-Type-type-gadt.B}\\ -\ocamlcodefragment{| \ocamltag{constructor}{C} : \hyperref[module-Type-type-variant_c]{\ocamlinlinecode{variant\_\allowbreak{}c}} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{module-Type-type-gadt.C}\\ +\label{Type-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{Type-type-gadt.A}\\ +\ocamlcodefragment{| \ocamltag{constructor}{B} : int \ocamltag{arrow}{$\rightarrow$} string \hyperref[Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{Type-type-gadt.B}\\ +\ocamlcodefragment{| \ocamltag{constructor}{C} : \hyperref[Type-type-variant_c]{\ocamlinlinecode{variant\_\allowbreak{}c}} \ocamltag{arrow}{$\rightarrow$} unit \hyperref[Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{Type-type-gadt.C}\\ \end{ocamltabular}% \\ -\label{module-Type-type-degenerate_gadt}\ocamlcodefragment{\ocamltag{keyword}{type} degenerate\_\allowbreak{}gadt = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : \hyperref[module-Type-type-degenerate_gadt]{\ocamlinlinecode{degenerate\_\allowbreak{}gadt}}}\label{module-Type-type-degenerate_gadt.A}\\ +\label{Type-type-degenerate_gadt}\ocamlcodefragment{\ocamltag{keyword}{type} degenerate\_\allowbreak{}gadt = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : \hyperref[Type-type-degenerate_gadt]{\ocamlinlinecode{degenerate\_\allowbreak{}gadt}}}\label{Type-type-degenerate_gadt.A}\\ \end{ocamltabular}% \\ -\label{module-Type-type-private_variant}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}variant = \ocamltag{keyword}{private} }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{module-Type-type-private_variant.A}\\ +\label{Type-type-private_variant}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}variant = \ocamltag{keyword}{private} }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{Type-type-private_variant.A}\\ \end{ocamltabular}% \\ -\label{module-Type-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{module-Type-type-record.a}& \\ -\ocamlinlinecode{\ocamltag{keyword}{mutable} b : int;\allowbreak{}}\label{module-Type-type-record.b}& \\ -\ocamlinlinecode{c : int;\allowbreak{}}\label{module-Type-type-record.c}& foo\\ -\ocamlinlinecode{d : int;\allowbreak{}}\label{module-Type-type-record.d}& \emph{bar}\\ -\ocamlinlinecode{e : 'a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{}}\label{module-Type-type-record.e}& \\ +\label{Type-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{Type-type-record.a}& \\ +\ocamlinlinecode{\ocamltag{keyword}{mutable} b : int;\allowbreak{}}\label{Type-type-record.b}& \\ +\ocamlinlinecode{c : int;\allowbreak{}}\label{Type-type-record.c}& foo\\ +\ocamlinlinecode{d : int;\allowbreak{}}\label{Type-type-record.d}& \emph{bar}\\ +\ocamlinlinecode{e : 'a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{}}\label{Type-type-record.e}& \\ \end{ocamltabular}% \\ \ocamlcodefragment{\}}\\ -\label{module-Type-type-polymorphic_variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A}\label{module-Type-type-polymorphic_variant.A}\\ -\ocamlcodefragment{| `B \ocamltag{keyword}{of} int}\label{module-Type-type-polymorphic_variant.B}\\ -\ocamlcodefragment{| `C \ocamltag{keyword}{of} int * unit}\label{module-Type-type-polymorphic_variant.C}\\ -\ocamlcodefragment{| `D}\label{module-Type-type-polymorphic_variant.D}\\ +\label{Type-type-polymorphic_variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A}\label{Type-type-polymorphic_variant.A}\\ +\ocamlcodefragment{| `B \ocamltag{keyword}{of} int}\label{Type-type-polymorphic_variant.B}\\ +\ocamlcodefragment{| `C \ocamltag{keyword}{of} int * unit}\label{Type-type-polymorphic_variant.C}\\ +\ocamlcodefragment{| `D}\label{Type-type-polymorphic_variant.D}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Type-type-polymorphic_variant_extension}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant\_\allowbreak{}extension = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \hyperref[module-Type-type-polymorphic_variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{module-Type-type-polymorphic_variant_extension.polymorphic_variant}\\ -\ocamlcodefragment{| `E}\label{module-Type-type-polymorphic_variant_extension.E}\\ +\label{Type-type-polymorphic_variant_extension}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant\_\allowbreak{}extension = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \hyperref[Type-type-polymorphic_variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{Type-type-polymorphic_variant_extension.polymorphic_variant}\\ +\ocamlcodefragment{| `E}\label{Type-type-polymorphic_variant_extension.E}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Type-type-nested_polymorphic_variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}polymorphic\_\allowbreak{}variant = [ }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A \ocamltag{keyword}{of} [ `B | `C ]}\label{module-Type-type-nested_polymorphic_variant.A}\\ +\label{Type-type-nested_polymorphic_variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}polymorphic\_\allowbreak{}variant = [ }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| `A \ocamltag{keyword}{of} [ `B | `C ]}\label{Type-type-nested_polymorphic_variant.A}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Type-type-private_extenion}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}extenion = \ocamltag{keyword}{private} [> }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \hyperref[module-Type-type-polymorphic_variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{module-Type-type-private_extenion.polymorphic_variant}\\ +\label{Type-type-private_extenion}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}extenion = \ocamltag{keyword}{private} [> }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \hyperref[Type-type-polymorphic_variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{Type-type-private_extenion.polymorphic_variant}\\ \end{ocamltabular}% \\ \ocamlcodefragment{ ]}\\ -\label{module-Type-type-object_}\ocamlcodefragment{\ocamltag{keyword}{type} object\_\allowbreak{} = < a : int ;\allowbreak{} b : int ;\allowbreak{} c : int >}\\ -\label{module-Type-module-type-X}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Type-module-type-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Type-module-type-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ -\label{module-Type-module-type-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{Type-type-object_}\ocamlcodefragment{\ocamltag{keyword}{type} object\_\allowbreak{} = < a : int ;\allowbreak{} b : int ;\allowbreak{} c : int >}\\ +\label{Type-module-type-X}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[Type-module-type-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{Type-module-type-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{Type-module-type-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Type-type-module_}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{} = (\ocamltag{keyword}{module} \hyperref[module-Type-module-type-X]{\ocamlinlinecode{X}})}\\ -\label{module-Type-type-module_substitution}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{}substitution = (\ocamltag{keyword}{module} \hyperref[module-Type-module-type-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[module-Type-module-type-X-type-t]{\ocamlinlinecode{t}} = int \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[module-Type-module-type-X-type-u]{\ocamlinlinecode{u}} = unit)}\\ -\label{module-Type-type-covariant}\ocamlcodefragment{\ocamltag{keyword}{type} +'a covariant}\\ -\label{module-Type-type-contravariant}\ocamlcodefragment{\ocamltag{keyword}{type} -'a contravariant}\\ -\label{module-Type-type-bivariant}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} bivariant = int}\\ -\label{module-Type-type-binary}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) binary}\\ -\label{module-Type-type-using_binary}\ocamlcodefragment{\ocamltag{keyword}{type} using\_\allowbreak{}binary = (int,\allowbreak{} int) \hyperref[module-Type-type-binary]{\ocamlinlinecode{binary}}}\\ -\label{module-Type-type-name}\ocamlcodefragment{\ocamltag{keyword}{type} 'custom name}\\ -\label{module-Type-type-constrained}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constrained = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int}\\ -\label{module-Type-type-exact_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [ `A | `B of int ]}\\ -\label{module-Type-type-lower_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `A | `B of int ]}\\ -\label{module-Type-type-any_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> ]}\\ -\label{module-Type-type-upper_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a upper\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< `A | `B of int ]}\\ -\label{module-Type-type-named_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a named\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< \hyperref[module-Type-type-polymorphic_variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}} ]}\\ -\label{module-Type-type-exact_object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int ;\allowbreak{} b : int >}\\ -\label{module-Type-type-lower_object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int ;\allowbreak{} b : int.\allowbreak{}.\allowbreak{} >}\\ -\label{module-Type-type-poly_object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : 'a.\allowbreak{} \ocamltag{type-var}{'a} >}\\ -\label{module-Type-type-double_constrained}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) double\_\allowbreak{}constrained = \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int \ocamltag{keyword}{constraint} \ocamltag{type-var}{'b} = unit}\\ -\label{module-Type-type-as_}\ocamlcodefragment{\ocamltag{keyword}{type} as\_\allowbreak{} = int \ocamltag{keyword}{as} 'a * \ocamltag{type-var}{'a}}\\ -\label{module-Type-type-extensible}\ocamlcodefragment{\ocamltag{keyword}{type} extensible = .\allowbreak{}.\allowbreak{}}\\ -\label{module-Type-extension-decl-Extension}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[module-Type-type-extensible]{\ocamlinlinecode{extensible}} += }\\ -\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Extension}}\label{module-Type-extension-Extension}& Documentation for \hyperref[module-Type-extension-Extension]{\ocamlinlinecode{\ocamlinlinecode{Extension}}[p\pageref*{module-Type-extension-Extension}]}.\\ -\ocamlcodefragment{| \ocamltag{extension}{Another\_\allowbreak{}extension}}\label{module-Type-extension-Another_extension}& Documentation for \hyperref[module-Type-extension-Another_extension]{\ocamlinlinecode{\ocamlinlinecode{Another\_\allowbreak{}extension}}[p\pageref*{module-Type-extension-Another_extension}]}.\\ +\label{Type-type-module_}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{} = (\ocamltag{keyword}{module} \hyperref[Type-module-type-X]{\ocamlinlinecode{X}})}\\ +\label{Type-type-module_substitution}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{}substitution = (\ocamltag{keyword}{module} \hyperref[Type-module-type-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[Type-module-type-X-type-t]{\ocamlinlinecode{t}} = int \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[Type-module-type-X-type-u]{\ocamlinlinecode{u}} = unit)}\\ +\label{Type-type-covariant}\ocamlcodefragment{\ocamltag{keyword}{type} +'a covariant}\\ +\label{Type-type-contravariant}\ocamlcodefragment{\ocamltag{keyword}{type} -'a contravariant}\\ +\label{Type-type-bivariant}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} bivariant = int}\\ +\label{Type-type-binary}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) binary}\\ +\label{Type-type-using_binary}\ocamlcodefragment{\ocamltag{keyword}{type} using\_\allowbreak{}binary = (int,\allowbreak{} int) \hyperref[Type-type-binary]{\ocamlinlinecode{binary}}}\\ +\label{Type-type-name}\ocamlcodefragment{\ocamltag{keyword}{type} 'custom name}\\ +\label{Type-type-constrained}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constrained = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int}\\ +\label{Type-type-exact_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [ `A | `B of int ]}\\ +\label{Type-type-lower_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `A | `B of int ]}\\ +\label{Type-type-any_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> ]}\\ +\label{Type-type-upper_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a upper\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< `A | `B of int ]}\\ +\label{Type-type-named_variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a named\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< \hyperref[Type-type-polymorphic_variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}} ]}\\ +\label{Type-type-exact_object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int ;\allowbreak{} b : int >}\\ +\label{Type-type-lower_object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int ;\allowbreak{} b : int.\allowbreak{}.\allowbreak{} >}\\ +\label{Type-type-poly_object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : 'a.\allowbreak{} \ocamltag{type-var}{'a} >}\\ +\label{Type-type-double_constrained}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) double\_\allowbreak{}constrained = \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int \ocamltag{keyword}{constraint} \ocamltag{type-var}{'b} = unit}\\ +\label{Type-type-as_}\ocamlcodefragment{\ocamltag{keyword}{type} as\_\allowbreak{} = int \ocamltag{keyword}{as} 'a * \ocamltag{type-var}{'a}}\\ +\label{Type-type-extensible}\ocamlcodefragment{\ocamltag{keyword}{type} extensible = .\allowbreak{}.\allowbreak{}}\\ +\label{Type-extension-decl-Extension}\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[Type-type-extensible]{\ocamlinlinecode{extensible}} += }\\ +\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Extension}}\label{Type-extension-Extension}& Documentation for \hyperref[Type-extension-Extension]{\ocamlinlinecode{\ocamlinlinecode{Extension}}[p\pageref*{Type-extension-Extension}]}.\\ +\ocamlcodefragment{| \ocamltag{extension}{Another\_\allowbreak{}extension}}\label{Type-extension-Another_extension}& Documentation for \hyperref[Type-extension-Another_extension]{\ocamlinlinecode{\ocamlinlinecode{Another\_\allowbreak{}extension}}[p\pageref*{Type-extension-Another_extension}]}.\\ \end{ocamltabular}% \\ -\label{module-Type-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{type} mutually = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[module-Type-type-recursive]{\ocamlinlinecode{recursive}}}\label{module-Type-type-mutually.A}\\ +\label{Type-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{type} mutually = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[Type-type-recursive]{\ocamlinlinecode{recursive}}}\label{Type-type-mutually.A}\\ \end{ocamltabular}% \\ -\label{module-Type-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{and} recursive = }\\ -\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} \hyperref[module-Type-type-mutually]{\ocamlinlinecode{mutually}}}\label{module-Type-type-recursive.B}\\ +\label{Type-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{and} recursive = }\\ +\begin{ocamltabular}{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} \hyperref[Type-type-mutually]{\ocamlinlinecode{mutually}}}\label{Type-type-recursive.B}\\ \end{ocamltabular}% \\ -\label{module-Type-exception-Foo}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Foo} \ocamltag{keyword}{of} int * int}\\ +\label{Type-exception-Foo}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Foo} \ocamltag{keyword}{of} int * int}\\ diff --git a/test/generators/latex/Val.tex b/test/generators/latex/Val.tex index c27a104cdb..82c0c7b9c3 100644 --- a/test/generators/latex/Val.tex +++ b/test/generators/latex/Val.tex @@ -1,8 +1,8 @@ -\section{Module \ocamlinlinecode{Val}}\label{module-Val}% -\label{module-Val-val-documented}\ocamlcodefragment{\ocamltag{keyword}{val} documented : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% +\section{Module \ocamlinlinecode{Val}}\label{Val}% +\label{Val-val-documented}\ocamlcodefragment{\ocamltag{keyword}{val} documented : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% \medbreak -\label{module-Val-val-undocumented}\ocamlcodefragment{\ocamltag{keyword}{val} undocumented : unit}\\ -\label{module-Val-val-documented_above}\ocamlcodefragment{\ocamltag{keyword}{val} documented\_\allowbreak{}above : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% +\label{Val-val-undocumented}\ocamlcodefragment{\ocamltag{keyword}{val} undocumented : unit}\\ +\label{Val-val-documented_above}\ocamlcodefragment{\ocamltag{keyword}{val} documented\_\allowbreak{}above : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% \medbreak diff --git a/test/generators/latex/mld.tex b/test/generators/latex/mld.tex index 20180bde0d..292f8bf062 100644 --- a/test/generators/latex/mld.tex +++ b/test/generators/latex/mld.tex @@ -1,4 +1,4 @@ -\section{Mld Page\label{mld-page}}\label{leaf-page-mld}% +\section{Mld Page\label{mld-page}}\label{mld}% This is an \ocamlinlinecode{.\allowbreak{}mld} file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. It will have a TOC generated from section headings. diff --git a/test/generators/link.dune.inc b/test/generators/link.dune.inc index eb2d15b02e..e50d6a5de1 100644 --- a/test/generators/link.dune.inc +++ b/test/generators/link.dune.inc @@ -1159,7 +1159,7 @@ (subdir man (rule - (targets Bugs_post_406.3o.gen Bugs_post_406.let_open'.3o.gen) + (targets Bugs_post_406.3o.gen Bugs_post_406.class-let_open'.3o.gen) (action (run odoc @@ -1180,7 +1180,9 @@ (rule (alias runtest) (action - (diff Bugs_post_406.let_open'.3o Bugs_post_406.let_open'.3o.gen)) + (diff + Bugs_post_406.class-let_open'.3o + Bugs_post_406.class-let_open'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.06)))) @@ -1489,10 +1491,10 @@ (rule (targets Class.3o.gen - Class.mutually'.3o.gen - Class.recursive'.3o.gen - Class.empty_virtual'.3o.gen - Class.polymorphic'.3o.gen) + Class.class-mutually'.3o.gen + Class.class-recursive'.3o.gen + Class.class-empty_virtual'.3o.gen + Class.class-polymorphic'.3o.gen) (action (run odoc man-generate -o . --extra-suffix gen %{dep:../class.odocl})) (enabled_if @@ -1506,25 +1508,25 @@ (rule (alias runtest) (action - (diff Class.mutually'.3o Class.mutually'.3o.gen)) + (diff Class.class-mutually'.3o Class.class-mutually'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04))) (rule (alias runtest) (action - (diff Class.recursive'.3o Class.recursive'.3o.gen)) + (diff Class.class-recursive'.3o Class.class-recursive'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04))) (rule (alias runtest) (action - (diff Class.empty_virtual'.3o Class.empty_virtual'.3o.gen)) + (diff Class.class-empty_virtual'.3o Class.class-empty_virtual'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04))) (rule (alias runtest) (action - (diff Class.polymorphic'.3o Class.polymorphic'.3o.gen)) + (diff Class.class-polymorphic'.3o Class.class-polymorphic'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04)))) @@ -1657,8 +1659,8 @@ (rule (targets Class_comments.3o.gen - Class_comments.x.3o.gen - Class_comments.c.3o.gen) + Class_comments.class-x.3o.gen + Class_comments.class-c.3o.gen) (action (run odoc @@ -1679,13 +1681,13 @@ (rule (alias runtest) (action - (diff Class_comments.x.3o Class_comments.x.3o.gen)) + (diff Class_comments.class-x.3o Class_comments.class-x.3o.gen)) (enabled_if (>= %{ocaml_version} 4.08))) (rule (alias runtest) (action - (diff Class_comments.c.3o Class_comments.c.3o.gen)) + (diff Class_comments.class-c.3o Class_comments.class-c.3o.gen)) (enabled_if (>= %{ocaml_version} 4.08)))) @@ -3050,7 +3052,7 @@ (subdir man (rule - (targets Labels.3o.gen Labels.A.3o.gen Labels.c.3o.gen) + (targets Labels.3o.gen Labels.A.3o.gen Labels.class-c.3o.gen) (action (run odoc man-generate -o . --extra-suffix gen %{dep:../labels.odocl})) (enabled_if @@ -3070,7 +3072,7 @@ (rule (alias runtest) (action - (diff Labels.c.3o Labels.c.3o.gen)) + (diff Labels.class-c.3o Labels.class-c.3o.gen)) (enabled_if (>= %{ocaml_version} 4.09)))) @@ -4569,8 +4571,8 @@ Nested.3o.gen Nested.X.3o.gen Nested.F.3o.gen - Nested.z.3o.gen - Nested.inherits.3o.gen) + Nested.class-z.3o.gen + Nested.class-inherits.3o.gen) (action (run odoc man-generate -o . --extra-suffix gen %{dep:../nested.odocl})) (enabled_if @@ -4596,13 +4598,13 @@ (rule (alias runtest) (action - (diff Nested.z.3o Nested.z.3o.gen)) + (diff Nested.class-z.3o Nested.class-z.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04))) (rule (alias runtest) (action - (diff Nested.inherits.3o Nested.inherits.3o.gen)) + (diff Nested.class-inherits.3o Nested.class-inherits.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04)))) @@ -6356,14 +6358,14 @@ Ocamlary.FunctorTypeOf.3o.gen Ocamlary.IncludedA.3o.gen Ocamlary.ExtMod.3o.gen - Ocamlary.empty_class.3o.gen - Ocamlary.one_method_class.3o.gen - Ocamlary.two_method_class.3o.gen - Ocamlary.param_class.3o.gen + Ocamlary.class-empty_class.3o.gen + Ocamlary.class-one_method_class.3o.gen + Ocamlary.class-two_method_class.3o.gen + Ocamlary.class-param_class.3o.gen Ocamlary.Dep1.3o.gen Ocamlary.Dep1.X.3o.gen Ocamlary.Dep1.X.Y.3o.gen - Ocamlary.Dep1.X.Y.c.3o.gen + Ocamlary.Dep1.X.Y.class-c.3o.gen Ocamlary.Dep2.3o.gen Ocamlary.Dep2.A.3o.gen Ocamlary.Dep3.3o.gen @@ -6381,7 +6383,7 @@ Ocamlary.Dep11.3o.gen Ocamlary.Dep12.3o.gen Ocamlary.Dep13.3o.gen - Ocamlary.Dep13.c.3o.gen + Ocamlary.Dep13.class-c.3o.gen Ocamlary.With2.3o.gen Ocamlary.With3.3o.gen Ocamlary.With3.N.3o.gen @@ -6528,25 +6530,29 @@ (rule (alias runtest) (action - (diff Ocamlary.empty_class.3o Ocamlary.empty_class.3o.gen)) + (diff Ocamlary.class-empty_class.3o Ocamlary.class-empty_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.one_method_class.3o Ocamlary.one_method_class.3o.gen)) + (diff + Ocamlary.class-one_method_class.3o + Ocamlary.class-one_method_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.two_method_class.3o Ocamlary.two_method_class.3o.gen)) + (diff + Ocamlary.class-two_method_class.3o + Ocamlary.class-two_method_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.param_class.3o Ocamlary.param_class.3o.gen)) + (diff Ocamlary.class-param_class.3o Ocamlary.class-param_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule @@ -6570,7 +6576,7 @@ (rule (alias runtest) (action - (diff Ocamlary.Dep1.X.Y.c.3o Ocamlary.Dep1.X.Y.c.3o.gen)) + (diff Ocamlary.Dep1.X.Y.class-c.3o Ocamlary.Dep1.X.Y.class-c.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule @@ -6678,7 +6684,7 @@ (rule (alias runtest) (action - (diff Ocamlary.Dep13.c.3o Ocamlary.Dep13.c.3o.gen)) + (diff Ocamlary.Dep13.class-c.3o Ocamlary.Dep13.class-c.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule @@ -8171,8 +8177,8 @@ Toplevel_comments.M'.3o.gen Toplevel_comments.M''.3o.gen Toplevel_comments.Alias.3o.gen - Toplevel_comments.c1.3o.gen - Toplevel_comments.c2.3o.gen + Toplevel_comments.class-c1.3o.gen + Toplevel_comments.class-c2.3o.gen Toplevel_comments.Ref_in_synopsis.3o.gen Toplevel_comments.Comments_on_open.3o.gen Toplevel_comments.Comments_on_open.M.3o.gen) @@ -8236,13 +8242,13 @@ (rule (alias runtest) (action - (diff Toplevel_comments.c1.3o Toplevel_comments.c1.3o.gen)) + (diff Toplevel_comments.class-c1.3o Toplevel_comments.class-c1.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04))) (rule (alias runtest) (action - (diff Toplevel_comments.c2.3o Toplevel_comments.c2.3o.gen)) + (diff Toplevel_comments.class-c2.3o Toplevel_comments.class-c2.3o.gen)) (enabled_if (>= %{ocaml_version} 4.04))) (rule diff --git a/test/generators/man/Bugs_post_406.let_open'.3o b/test/generators/man/Bugs_post_406.class-let_open'.3o similarity index 100% rename from test/generators/man/Bugs_post_406.let_open'.3o rename to test/generators/man/Bugs_post_406.class-let_open'.3o diff --git a/test/generators/man/Class.empty_virtual'.3o b/test/generators/man/Class.class-empty_virtual'.3o similarity index 100% rename from test/generators/man/Class.empty_virtual'.3o rename to test/generators/man/Class.class-empty_virtual'.3o diff --git a/test/generators/man/Class.mutually'.3o b/test/generators/man/Class.class-mutually'.3o similarity index 100% rename from test/generators/man/Class.mutually'.3o rename to test/generators/man/Class.class-mutually'.3o diff --git a/test/generators/man/Class.polymorphic'.3o b/test/generators/man/Class.class-polymorphic'.3o similarity index 100% rename from test/generators/man/Class.polymorphic'.3o rename to test/generators/man/Class.class-polymorphic'.3o diff --git a/test/generators/man/Class.recursive'.3o b/test/generators/man/Class.class-recursive'.3o similarity index 100% rename from test/generators/man/Class.recursive'.3o rename to test/generators/man/Class.class-recursive'.3o diff --git a/test/generators/man/Class_comments.c.3o b/test/generators/man/Class_comments.class-c.3o similarity index 100% rename from test/generators/man/Class_comments.c.3o rename to test/generators/man/Class_comments.class-c.3o diff --git a/test/generators/man/Class_comments.x.3o b/test/generators/man/Class_comments.class-x.3o similarity index 100% rename from test/generators/man/Class_comments.x.3o rename to test/generators/man/Class_comments.class-x.3o diff --git a/test/generators/man/Labels.c.3o b/test/generators/man/Labels.class-c.3o similarity index 100% rename from test/generators/man/Labels.c.3o rename to test/generators/man/Labels.class-c.3o diff --git a/test/generators/man/Nested.inherits.3o b/test/generators/man/Nested.class-inherits.3o similarity index 100% rename from test/generators/man/Nested.inherits.3o rename to test/generators/man/Nested.class-inherits.3o diff --git a/test/generators/man/Nested.z.3o b/test/generators/man/Nested.class-z.3o similarity index 100% rename from test/generators/man/Nested.z.3o rename to test/generators/man/Nested.class-z.3o diff --git a/test/generators/man/Ocamlary.Dep1.X.Y.c.3o b/test/generators/man/Ocamlary.Dep1.X.Y.class-c.3o similarity index 100% rename from test/generators/man/Ocamlary.Dep1.X.Y.c.3o rename to test/generators/man/Ocamlary.Dep1.X.Y.class-c.3o diff --git a/test/generators/man/Ocamlary.Dep13.c.3o b/test/generators/man/Ocamlary.Dep13.class-c.3o similarity index 100% rename from test/generators/man/Ocamlary.Dep13.c.3o rename to test/generators/man/Ocamlary.Dep13.class-c.3o diff --git a/test/generators/man/Ocamlary.empty_class.3o b/test/generators/man/Ocamlary.class-empty_class.3o similarity index 100% rename from test/generators/man/Ocamlary.empty_class.3o rename to test/generators/man/Ocamlary.class-empty_class.3o diff --git a/test/generators/man/Ocamlary.one_method_class.3o b/test/generators/man/Ocamlary.class-one_method_class.3o similarity index 100% rename from test/generators/man/Ocamlary.one_method_class.3o rename to test/generators/man/Ocamlary.class-one_method_class.3o diff --git a/test/generators/man/Ocamlary.param_class.3o b/test/generators/man/Ocamlary.class-param_class.3o similarity index 100% rename from test/generators/man/Ocamlary.param_class.3o rename to test/generators/man/Ocamlary.class-param_class.3o diff --git a/test/generators/man/Ocamlary.two_method_class.3o b/test/generators/man/Ocamlary.class-two_method_class.3o similarity index 100% rename from test/generators/man/Ocamlary.two_method_class.3o rename to test/generators/man/Ocamlary.class-two_method_class.3o diff --git a/test/generators/man/Toplevel_comments.c1.3o b/test/generators/man/Toplevel_comments.class-c1.3o similarity index 100% rename from test/generators/man/Toplevel_comments.c1.3o rename to test/generators/man/Toplevel_comments.class-c1.3o diff --git a/test/generators/man/Toplevel_comments.c2.3o b/test/generators/man/Toplevel_comments.class-c2.3o similarity index 100% rename from test/generators/man/Toplevel_comments.c2.3o rename to test/generators/man/Toplevel_comments.class-c2.3o diff --git a/test/generators/man/bugs_post_406.targets b/test/generators/man/bugs_post_406.targets index 86c4657323..1443a247d4 100644 --- a/test/generators/man/bugs_post_406.targets +++ b/test/generators/man/bugs_post_406.targets @@ -1,2 +1,2 @@ Bugs_post_406.3o -Bugs_post_406.let_open'.3o +Bugs_post_406.class-let_open'.3o diff --git a/test/generators/man/class.targets b/test/generators/man/class.targets index 9b224aac95..b82465c59d 100644 --- a/test/generators/man/class.targets +++ b/test/generators/man/class.targets @@ -1,5 +1,5 @@ Class.3o -Class.mutually'.3o -Class.recursive'.3o -Class.empty_virtual'.3o -Class.polymorphic'.3o +Class.class-mutually'.3o +Class.class-recursive'.3o +Class.class-empty_virtual'.3o +Class.class-polymorphic'.3o diff --git a/test/generators/man/class_comments.targets b/test/generators/man/class_comments.targets index c5f0ebef85..c9a8f499ab 100644 --- a/test/generators/man/class_comments.targets +++ b/test/generators/man/class_comments.targets @@ -1,3 +1,3 @@ Class_comments.3o -Class_comments.x.3o -Class_comments.c.3o +Class_comments.class-x.3o +Class_comments.class-c.3o diff --git a/test/generators/man/labels.targets b/test/generators/man/labels.targets index 093cd44447..ea0f3927c5 100644 --- a/test/generators/man/labels.targets +++ b/test/generators/man/labels.targets @@ -1,3 +1,3 @@ Labels.3o Labels.A.3o -Labels.c.3o +Labels.class-c.3o diff --git a/test/generators/man/nested.targets b/test/generators/man/nested.targets index de9e50918c..ccb23f11bf 100644 --- a/test/generators/man/nested.targets +++ b/test/generators/man/nested.targets @@ -1,5 +1,5 @@ Nested.3o Nested.X.3o Nested.F.3o -Nested.z.3o -Nested.inherits.3o +Nested.class-z.3o +Nested.class-inherits.3o diff --git a/test/generators/man/ocamlary.targets b/test/generators/man/ocamlary.targets index c5704353d3..0da00edb3f 100644 --- a/test/generators/man/ocamlary.targets +++ b/test/generators/man/ocamlary.targets @@ -13,14 +13,14 @@ Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o Ocamlary.FunctorTypeOf.3o Ocamlary.IncludedA.3o Ocamlary.ExtMod.3o -Ocamlary.empty_class.3o -Ocamlary.one_method_class.3o -Ocamlary.two_method_class.3o -Ocamlary.param_class.3o +Ocamlary.class-empty_class.3o +Ocamlary.class-one_method_class.3o +Ocamlary.class-two_method_class.3o +Ocamlary.class-param_class.3o Ocamlary.Dep1.3o Ocamlary.Dep1.X.3o Ocamlary.Dep1.X.Y.3o -Ocamlary.Dep1.X.Y.c.3o +Ocamlary.Dep1.X.Y.class-c.3o Ocamlary.Dep2.3o Ocamlary.Dep2.A.3o Ocamlary.Dep3.3o @@ -38,7 +38,7 @@ Ocamlary.Dep9.3o Ocamlary.Dep11.3o Ocamlary.Dep12.3o Ocamlary.Dep13.3o -Ocamlary.Dep13.c.3o +Ocamlary.Dep13.class-c.3o Ocamlary.With2.3o Ocamlary.With3.3o Ocamlary.With3.N.3o diff --git a/test/generators/man/toplevel_comments.targets b/test/generators/man/toplevel_comments.targets index 0123faa972..7292226fa4 100644 --- a/test/generators/man/toplevel_comments.targets +++ b/test/generators/man/toplevel_comments.targets @@ -5,8 +5,8 @@ Toplevel_comments.M.3o Toplevel_comments.M'.3o Toplevel_comments.M''.3o Toplevel_comments.Alias.3o -Toplevel_comments.c1.3o -Toplevel_comments.c2.3o +Toplevel_comments.class-c1.3o +Toplevel_comments.class-c2.3o Toplevel_comments.Ref_in_synopsis.3o Toplevel_comments.Comments_on_open.3o Toplevel_comments.Comments_on_open.M.3o diff --git a/test/xref2/github_issue_857.t/run.t b/test/xref2/github_issue_857.t/run.t index 1fa774b121..3fc4b74a8d 100644 --- a/test/xref2/github_issue_857.t/run.t +++ b/test/xref2/github_issue_857.t/run.t @@ -10,8 +10,8 @@ A quick test to repro the issue found in #857 In latex, labels in subpages should be disambiguated since the subpage is inlined inside the generated latex source. $ cat latex/A.tex | sed 's/\\/\n\\/g' | grep label - \label{module-A}% - \label{module-A-module-type-A} + \label{A}% + \label{A-module-type-A} \label{first}}% \label{first_2}}% diff --git a/test/xref2/map_ref_to_url.t/run.t b/test/xref2/map_ref_to_url.t/run.t index 7d415ad5d8..9a05bd13cf 100644 --- a/test/xref2/map_ref_to_url.t/run.t +++ b/test/xref2/map_ref_to_url.t/run.t @@ -13,7 +13,7 @@ The root-url argument prepends a string to the html url Generate latex url $ odoc latex-url -I . Foo.t - page-test-module-Foo-type-t + test-Foo-type-t When the reference cannot be resolved. $ odoc html-url -I . Foo.u From 6fb5c4781030326b9ed6ec5300dc06a9b2c24fd6 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 26 Aug 2024 15:07:56 +0200 Subject: [PATCH 2/3] Update Changes Co-authored-by: panglesd --- CHANGES.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/CHANGES.md b/CHANGES.md index 74fb71fd79..592ea5ee6e 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -42,6 +42,8 @@ - Allow `][` in code blocks (@Julow, #1149) This was interpreted as "code blocks with result", which now mandate a delimiter: `{delim@lang[ code ]delim[ result ]}` +- Output file paths and labels in the man and latex backends changed to avoid name clashes + (@Julow, #1191) ### Fixed From 40026bf9a08b26de13cc522782c766310270bd07 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 4 Sep 2024 15:02:53 +0200 Subject: [PATCH 3/3] Rename and clarify 'pp_disambiguating_prefix' Co-authored-by: Paul-Elliot --- src/document/url.ml | 2 +- src/document/url.mli | 5 +++-- src/html/link.ml | 2 +- src/latex/generator.ml | 2 +- src/manpage/link.ml | 2 +- 5 files changed, 7 insertions(+), 6 deletions(-) diff --git a/src/document/url.ml b/src/document/url.ml index 0e4bfb01ac..4c3f3847c9 100644 --- a/src/document/url.ml +++ b/src/document/url.ml @@ -115,7 +115,7 @@ module Path = struct let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind) - let pp_kind_prefix_for_output fmt = function + let pp_disambiguating_prefix fmt = function | `Module | `Page | `LeafPage | `File | `SourcePage -> () | kind -> Format.fprintf fmt "%s-" (string_of_kind kind) diff --git a/src/document/url.mli b/src/document/url.mli index 2b13e4de8e..4dabe5365f 100644 --- a/src/document/url.mli +++ b/src/document/url.mli @@ -27,8 +27,9 @@ module Path : sig val string_of_kind : kind -> string - val pp_kind_prefix_for_output : Format.formatter -> kind -> unit - (** Print the ["kind-"] prefix used in output files. *) + val pp_disambiguating_prefix : Format.formatter -> kind -> unit + (** Print the ["kind-"] prefix used to disambiguate urls in "flat modes": + e.g. latex labels and output files in [--flat] HTML and man output *) type t = { kind : kind; parent : t option; name : string } diff --git a/src/html/link.ml b/src/html/link.ml index dba7b7d3d9..f0724694e3 100644 --- a/src/html/link.ml +++ b/src/html/link.ml @@ -5,7 +5,7 @@ module Path = struct let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = - Format.asprintf "%a%s" Url.Path.pp_kind_prefix_for_output kind name + Format.asprintf "%a%s" Url.Path.pp_disambiguating_prefix kind name let is_leaf_page url = url.Url.Path.kind = `LeafPage diff --git a/src/latex/generator.ml b/src/latex/generator.ml index 0ba76c2f8f..5cd04bb52f 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -10,7 +10,7 @@ module Link = struct | None -> () in Format.fprintf ppf "%a%a%s" pp_parent x.parent - Url.Path.pp_kind_prefix_for_output x.kind x.name + Url.Path.pp_disambiguating_prefix x.kind x.name let page p = Format.asprintf "%a" flatten_path p diff --git a/src/manpage/link.ml b/src/manpage/link.ml index 3fd606b29e..2e577028ec 100644 --- a/src/manpage/link.ml +++ b/src/manpage/link.ml @@ -3,7 +3,7 @@ open Odoc_document let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = - Format.asprintf "%a%s" Url.Path.pp_kind_prefix_for_output kind name + Format.asprintf "%a%s" Url.Path.pp_disambiguating_prefix kind name let as_filename ?(add_ext = true) (url : Url.Path.t) = let components = Url.Path.to_list url in