diff --git a/src/latex/dune b/src/latex/dune index 8023865ba1..3f5293ffa8 100644 --- a/src/latex/dune +++ b/src/latex/dune @@ -3,4 +3,4 @@ (public_name odoc.latex) (instrumentation (backend bisect_ppx)) - (libraries odoc_model odoc_document odoc_compat)) + (libraries odoc_model odoc_document odoc_compat fmt fpath)) diff --git a/src/latex/generator.ml b/src/latex/generator.ml index d98774a158..d799b3e47a 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -1,5 +1,5 @@ open Odoc_document.Types - +open Types module Doctree = Odoc_document.Doctree let rec list_concat_map ?sep ~f = function @@ -12,95 +12,6 @@ let rec list_concat_map ?sep ~f = function | None -> hd @ tl | Some sep -> hd @ sep :: tl - -type break_hierarchy = - | Aesthetic - | Simple - | Line - | Paragraph - | Separation - - -type row_size = - | Empty - | Small (** text only *) - | Large (** No table *) - | Huge (** tables **) - -type elt = - | Txt of string list - | Section of section - | Verbatim of string - | Internal_ref of reference - | External_ref of string * t option - | Label of string - | Raw of string - | Tag of string * t - | Style of [`Emphasis|`Bold|`Superscript|`Subscript|`Italic] * t - | Code_block of t - | Inlined_code of t - | Code_fragment of t - | Break of break_hierarchy - | List of list_info - | Description of (t * t) list - | Indented of t - | Table of table - | Ligaturable of string - -and section = {level:int; label:string option; content:t } -and list_info = { typ : Block.list_type; items: t list } -and table = { row_size: row_size; tbl: t list list} - - -and t = elt list -and reference = { short:bool; target:string; text: t option } -let const s ppf = Fmt.pf ppf s - - -let option ppf pp = Fmt.pf ppf "[%t]" pp -let macro name ?(options=[]) pp ppf content = - Fmt.pf ppf {|\%s%a{%a}|} name - (Fmt.list option) options - pp content - -let escape_text ~code_hyphenation = - let b = Buffer.create 17 in - fun s -> - for i = 0 to String.length s - 1 do - match s.[i] with - | '{' -> Buffer.add_string b "\\{" - | '}' -> Buffer.add_string b "\\}" - | '\\' -> Buffer.add_string b "\\textbackslash{}" - | '%' -> Buffer.add_string b "\\%" - | '~' -> Buffer.add_string b "\\textasciitilde{}" - | '^' -> Buffer.add_string b "\\textasciicircum{}" - | '_' -> - if code_hyphenation then Buffer.add_string b {|\_\allowbreak{}|} - else Buffer.add_string b {|\_|} - | '.' when code_hyphenation -> Buffer.add_string b {|.\allowbreak{}|} - | ';' when code_hyphenation -> Buffer.add_string b {|;\allowbreak{}|} - | ',' when code_hyphenation -> Buffer.add_string b {|,\allowbreak{}|} - - | '&' -> Buffer.add_string b "\\&" - | '#' -> Buffer.add_string b "\\#" - | '$' -> Buffer.add_string b "\\$" - - - | c -> Buffer.add_char b c - done; - let s = Buffer.contents b in - Buffer.reset b; - s - -let escape_ref ppf s = - for i = 0 to String.length s - 1 do - match s.[i] with - | '~' -> Fmt.pf ppf "+t+" - | '_' -> Fmt.pf ppf "+u+" - | '+' -> Fmt.pf ppf "+++" - | c -> Fmt.pf ppf "%c" c - done - module Link = struct let rec flatten_path ppf (x: Odoc_document.Url.Path.t) = match x.parent with @@ -148,99 +59,49 @@ module Link = struct end -let bind pp x ppf = pp ppf x -let mlabel ppf = macro "label" escape_ref ppf -let mbegin ?options = macro "begin" ?options Fmt.string -let mend = macro "end" Fmt.string -let code_fragment = macro "codefragment" -let break ppf level = - let pre: _ format6 = match level with - | Aesthetic -> "%%" - | Line -> {|\\|} - | Separation -> {|\medbreak|} - | _ -> "" in - let post: _ format6 = match level with - | Line | Separation | Aesthetic | Simple -> "" - | Paragraph -> "@," in - Fmt.pf ppf (pre ^^ "@," ^^ post) - - -let env name pp ?(with_break=false) ?(opts=[]) ?(args=[]) ppf content = - mbegin ppf name; - List.iter (Fmt.pf ppf "[%t]") opts; - List.iter (Fmt.pf ppf "{%t}") args; - pp ppf content; - mend ppf name; - break ppf (if with_break then Simple else Aesthetic) - -let indent pp ppf x = env "ocamlindent" pp ppf x -let inline_code = macro "inlinecode" -let verbatim = env "verbatim" Fmt.string - -let mhyperref pp r ppf = +let style = function + | `Emphasis | `Italic -> Raw.emph + | `Bold -> Raw.bold + | `Subscript -> Raw.subscript + | `Superscript -> Raw.superscript + +let gen_hyperref pp r ppf = match r.target, r.text with | "", None -> () - | "", Some content -> inline_code pp ppf content + | "", Some content -> Raw.inline_code pp ppf content | s, None -> - macro "ref" escape_ref ppf s + Raw.ref ppf s | s, Some content -> let pp = - if r.short then inline_code pp else - fun ppf x -> Fmt.pf ppf "%a[p%a]" (inline_code pp) x (macro "pageref*" escape_ref) s in - macro "hyperref" ~options:[bind escape_ref s] pp ppf content + if r.short then Raw.inline_code pp else + fun ppf x -> Fmt.pf ppf "%a[p%a]" (Raw.inline_code pp) x Raw.pageref_star s in + Raw.hyperref s pp ppf content let label = function | None -> [] | Some x (* {Odoc_document.Url.Anchor.anchor ; page; _ }*) -> [Label (Link.label x)] - - -let mstyle = function - | `Emphasis | `Italic -> macro "emph" - | `Bold -> macro "textbf" - | `Subscript -> macro "textsubscript" - | `Superscript -> macro "textsuperscript" - - -let code_block pp ppf x = - let name = "ocamlcodeblock" in - mbegin ppf name; - Fmt.cut ppf (); - pp ppf x; - Fmt.cut ppf (); - mend ppf name - let level_macro = function - | 0 -> macro "section" - | 1 -> macro "subsection" - | 2 -> macro "subsubsection" - | 3 | _ -> macro "subsubsection" + | 0 -> Raw.section + | 1 -> Raw.subsection + | 2 -> Raw.subsubsection + | 3 | _ -> Raw.subsubsection let none _ppf () = () let list kind pp ppf x = let list = match kind with - | Block.Ordered -> env "enumerate" - | Unordered -> env "itemize" in - let elt ppf = macro "item" pp ppf in + | Block.Ordered -> Raw.enumerate + | Unordered -> Raw.itemize in + let elt ppf = Raw.item pp ppf in match x with | [] -> (* empty list are not supported *) () | _ -> - list - (Fmt.list ~sep:(fun ppf () -> break ppf Aesthetic) elt) - ppf - x - -let description pp ppf x = - let elt ppf (d,elt) = macro "item" ~options:[bind pp d] pp ppf elt in - let all ppf x = - Fmt.pf ppf - {|\kern-\topsep -\makeatletter\advance\%@topsepadd-\topsep\makeatother%% topsep is hardcoded -|}; - Fmt.list ~sep:(fun ppf () -> break ppf Aesthetic) elt ppf x in - env "description" all ppf x + list + (Fmt.list ~sep:(fun ppf () -> Raw.break ppf Aesthetic) elt) + ppf + x let escape_entity = function @@ -276,7 +137,7 @@ let table = function let txt ~verbatim ~in_source ws = if verbatim then [Txt ws] else - let escaped = List.map (escape_text ~code_hyphenation:in_source) ws in + let escaped = List.map (Raw.Escape.text ~code_hyphenation:in_source) ws in match List.filter ( (<>) "" ) escaped with | [] -> [] | l -> [ Txt l ] @@ -295,26 +156,26 @@ let rec pp_elt ppf = function pp ppf content; match label with | None -> () - | Some label -> mlabel ppf label in + | Some label -> Raw.label ppf label in level_macro level with_label ppf (label,content) - | Break lvl -> break ppf lvl + | Break lvl -> Raw.break ppf lvl | Raw s -> Fmt.string ppf s - | Tag (x,t) -> env ~with_break:true x pp ppf t - | Verbatim s -> verbatim ppf s + | Verbatim s -> Raw.verbatim ppf s | Internal_ref r -> hyperref ppf r | External_ref (l,x) -> href ppf (l,x) - | Style (s,x) -> mstyle s pp ppf x + | Style (s,x) -> style s pp ppf x | Code_block [] -> () - | Code_block x -> code_block pp ppf x - | Inlined_code x -> inline_code pp ppf x - | Code_fragment x -> code_fragment pp ppf x + | Code_block x -> Raw.code_block pp ppf x + | Inlined_code x -> Raw.inline_code pp ppf x + | Code_fragment x -> Raw.code_fragment pp ppf x | List {typ; items} -> list typ pp ppf items - | Description items -> description pp ppf items + | Description items -> Raw.description pp ppf items | Table { row_size=Large|Huge as size; tbl } -> large_table size ppf tbl - | Table { row_size=Small|Empty; tbl } -> small_table ppf tbl - | Label x -> mlabel ppf x - | Indented x -> indent pp ppf x + | Table { row_size=Small|Empty; tbl } -> Raw.small_table pp ppf tbl + | Label x -> Raw.label ppf x + | Indented x -> Raw.indent pp ppf x | Ligaturable s -> Fmt.string ppf s + | Tag(s,t) -> tag s ppf t and pp ppf = function | [] -> () @@ -324,52 +185,35 @@ and pp ppf = function | Break a :: (Break b :: q) -> pp ppf ( Break (max a b) :: q) | Ligaturable "-" :: Ligaturable ">" :: q -> - Fmt.string ppf {|$\rightarrow$|}; pp ppf q + Raw.rightarrow ppf; pp ppf q | a :: q -> pp_elt ppf a; pp ppf q -and hyperref ppf r = mhyperref pp r ppf +and hyperref ppf r = gen_hyperref pp r ppf and href ppf (l,txt) = - let url ppf s = macro "url" Fmt.string ppf (escape_text ~code_hyphenation:false s) in - let footnote = macro "footnote" url in match txt with | Some txt -> - Fmt.pf ppf {|\href{%s}{%a}%a|} (escape_text ~code_hyphenation:false l) pp txt footnote l - | None -> url ppf l + Raw.href l pp ppf txt; Raw.footnote ppf l + | None -> Raw.url ppf l and large_table size ppf tbl = let rec row ppf = function - | [] -> break ppf Line + | [] -> Raw.break ppf Line | [a] -> pp ppf a | a :: (_ :: _ as q) -> Fmt.pf ppf "%a%a%a" pp a - break Aesthetic - (indent row) q in + Raw.break Aesthetic + (Raw.indent row) q in let matrix ppf m = List.iter (row ppf) m in match size with - | Huge -> break ppf Line; matrix ppf tbl - | Large | _ -> indent matrix ppf tbl - -and small_table ppf tbl = - let columns = List.length (List.hd tbl) in - let row ppf x = - let ampersand ppf () = Fmt.pf ppf "& " in - Fmt.list ~sep:ampersand pp ppf x; - break ppf Line in - let matrix ppf m = List.iter (row ppf) m in - let rec repeat n s ppf = if n = 0 then () else - Fmt.pf ppf "%t%t" s (repeat (n - 1) s) in - let cell ppf = Fmt.pf ppf "p{%.3f\\textwidth}" (1.0 /. float_of_int columns) in - let table ppf tbl = env "longtable" - ~opts:[const "l"] - ~args:[ repeat columns cell ] - matrix ppf tbl in - Fmt.pf ppf {|{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}%a}|} - table tbl + | Huge -> Raw.break ppf Line; matrix ppf tbl + | Large | _ -> Raw.indent matrix ppf tbl + +and tag s ppf x = Raw.ocamltag s pp ppf x let raw_markup (t : Raw_markup.t) = let target, content = t in @@ -381,7 +225,7 @@ let source k (t : Source.t) = let rec token (x : Source.token) = match x with | Elt i -> k i | Tag (None, l) -> tokens l - | Tag (Some s, l) -> [Tag(s, tokens l)] + | Tag(Some s,l) -> [Tag (s, tokens l)] and tokens t = list_concat_map t ~f:token in tokens t @@ -532,7 +376,7 @@ let rec documentedSrc (t : DocumentedSrc.t) = and items l = - let[@tailrec] rec walk_items + let rec walk_items ~only_text acc (t : Item.t list) = let continue_with rest elts = walk_items ~only_text (List.rev_append elts acc) rest @@ -575,14 +419,10 @@ and items l = module Doc = struct -(** Latex uses forward slash even on Windows. *) -let latex_path ppf path = - let path_s = String.concat "/" (Fpath.segs path) in - Fmt.string ppf path_s let link_children ppf children = let input_child ppf child = - macro "input" latex_path ppf child.Odoc_document.Renderer.filename + Raw.input ppf child.Odoc_document.Renderer.filename in Fmt.list input_child ppf children diff --git a/src/latex/raw.ml b/src/latex/raw.ml new file mode 100644 index 0000000000..ea93f27fb1 --- /dev/null +++ b/src/latex/raw.ml @@ -0,0 +1,167 @@ +(** Raw latex primitives: + - macro definitions + - env defitions + - text escaping +*) + +type pr = Format.formatter -> unit +type 'a with_options = ?options:pr list -> 'a +type ('a,'b) tr = 'a Fmt.t -> 'b Fmt.t +type 'a t = ('a,'a) tr + +module Escape = struct + let text ~code_hyphenation = + let b = Buffer.create 17 in + fun s -> + for i = 0 to String.length s - 1 do + match s.[i] with + | '{' -> Buffer.add_string b "\\{" + | '}' -> Buffer.add_string b "\\}" + | '\\' -> Buffer.add_string b "\\textbackslash{}" + | '%' -> Buffer.add_string b "\\%" + | '~' -> Buffer.add_string b "\\textasciitilde{}" + | '^' -> Buffer.add_string b "\\textasciicircum{}" + | '_' -> + if code_hyphenation then Buffer.add_string b {|\_\allowbreak{}|} + else Buffer.add_string b {|\_|} + | '.' when code_hyphenation -> Buffer.add_string b {|.\allowbreak{}|} + | ';' when code_hyphenation -> Buffer.add_string b {|;\allowbreak{}|} + | ',' when code_hyphenation -> Buffer.add_string b {|,\allowbreak{}|} + + | '&' -> Buffer.add_string b "\\&" + | '#' -> Buffer.add_string b "\\#" + | '$' -> Buffer.add_string b "\\$" + + + | c -> Buffer.add_char b c + done; + let s = Buffer.contents b in + Buffer.reset b; + s + + let pp ~code_hyphenation ppf x = Format.pp_print_string ppf (text ~code_hyphenation x) + + let ref ppf s = + for i = 0 to String.length s - 1 do + match s.[i] with + | '~' -> Fmt.pf ppf "+t+" + | '_' -> Fmt.pf ppf "+u+" + | '+' -> Fmt.pf ppf "+++" + | c -> Fmt.pf ppf "%c" c + done +end + +let option ppf pp = Fmt.pf ppf "[%t]" pp +let create name ?(options=[]) pp ppf content = + Fmt.pf ppf {|\%s%a{%a}|} name + (Fmt.list option) options + pp content + +let math name ppf = Fmt.pf ppf {|$\%s$|} name +let create2 name ?(options=[]) pp_x pp_y ppf x y = + Fmt.pf ppf {|\%s%a{%a}{%a}|} name + (Fmt.list option) options + pp_x x pp_y y + + +let bind pp x ppf = pp ppf x +let label ppf = create "label" Escape.ref ppf +let mbegin ?options = create "begin" ?options Fmt.string +let mend = create "end" Fmt.string +let code_fragment pp = create "ocamlcodefragment" pp +let break ppf level = + let pre: _ format6 = match level with + | Types.Aesthetic -> "%%" + | Line -> {|\\|} + | Separation -> {|\medbreak|} + | _ -> "" in + let post: _ format6 = match level with + | Types.Line | Separation | Aesthetic | Simple -> "" + | Paragraph -> "@," in + Fmt.pf ppf (pre ^^ "@," ^^ post) +let env name pp ?(with_break=false) ?(opts=[]) ?(args=[]) ppf content = + mbegin ppf name; + List.iter (Fmt.pf ppf "[%t]") opts; + List.iter (Fmt.pf ppf "{%t}") args; + pp ppf content; + mend ppf name; + break ppf (if with_break then Simple else Aesthetic) + +let indent pp ppf x = env "ocamlindent" pp ppf x +let inline_code pp = create "ocamlinlinecode" pp +let verbatim ppf x = env "verbatim" Fmt.string ppf x +let pageref_star x = create "pageref*" Escape.ref x +let hyperref s = create "hyperref" ~options:[bind Escape.ref s] +let ref x = create "ref" Escape.ref x + +let emph pp = create "emph" pp +let bold pp = create "bold" pp +let subscript pp = create "textsubscript" pp +let superscript pp = create "textsuperscript" pp + +let code_block pp ppf x = + let name = "ocamlcodeblock" in + mbegin ppf name; + Fmt.cut ppf (); + pp ppf x; + Fmt.cut ppf (); + mend ppf name + +let section pp = create "section" pp +let subsection pp = create "subsection" pp +let subsubsection pp = create "subsubsection" pp +let paragraph pp = create "paragraph" pp + +let enumerate pp ppf x = env "enumerate" pp ppf x +let itemize pp ppf x = env "itemize" pp ppf x +let raw_description pp ppf x = env "description" pp ppf x +let href x pp ppf y = create2 "href" (Escape.pp ~code_hyphenation:false) pp ppf x y +let item ?options = create "item" ?options + +let description pp ppf x = + let elt ppf (d,elt) = item ~options:[bind pp d] pp ppf elt in + let all ppf x = + Fmt.pf ppf + {|\kern-\topsep +\makeatletter\advance\%@topsepadd-\topsep\makeatother%% topsep is hardcoded +|}; + Fmt.list ~sep:(fun ppf () -> break ppf Aesthetic) elt ppf x in + raw_description all ppf x + +let url ppf s = create "url" Fmt.string ppf (Escape.text ~code_hyphenation:false s) +let footnote x = create "footnote" url x +let rightarrow ppf = math "rightarrow" ppf + +(** Latex uses forward slash even on Windows. *) +let latex_path ppf path = + let path_s = String.concat "/" (Fpath.segs path) in + Fmt.string ppf path_s +let input ppf x = create "input" latex_path ppf x + +let const s ppf = Fmt.pf ppf s + +let longtable ~column_desc pp ppf x = + env "ocamllongtable" + ~opts:[const "l"] + ~args:[ column_desc ] + pp ppf x + +let small_table pp ppf tbl = + let columns = List.length (List.hd tbl) in + let row ppf x = + let ampersand ppf () = Fmt.pf ppf "& " in + Fmt.list ~sep:ampersand pp ppf x; + break ppf Line in + let matrix ppf m = List.iter (row ppf) m in + let rec repeat n s ppf = if n = 0 then () else + Fmt.pf ppf "%t%t" s (repeat (n - 1) s) in + let cell ppf = Fmt.pf ppf "p{%.3f\\textwidth}" (1.0 /. float_of_int columns) in + let table ppf tbl = + longtable + (repeat columns cell) + matrix ppf tbl in + Fmt.pf ppf {|{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}%a}|} + table tbl + +let ocamltag tag pp ppf x = + create2 "ocamltag" Fmt.string pp ppf tag x diff --git a/src/latex/raw.mli b/src/latex/raw.mli new file mode 100644 index 0000000000..5aeb0502b6 --- /dev/null +++ b/src/latex/raw.mli @@ -0,0 +1,76 @@ +(** Raw latex primitives: + - macro and environment definitions + - text escaping +*) + +(** {1 Helper types } *) +type pr = Format.formatter -> unit +type 'a with_options = ?options:pr list -> 'a +type ('a,'b) tr = 'a Fmt.t -> 'b Fmt.t +type 'a t = ('a,'a) tr + +(** {1 Helper functions } *) +module Escape: sig + val text: code_hyphenation:bool -> string -> string + val ref: string Fmt.t +end + +val break: Types.break_hierarchy Fmt.t +val rightarrow: pr + +val label: string Fmt.t +val verbatim: string Fmt.t + + +val pageref_star: string Fmt.t +val hyperref: string -> 'a t +val href: string -> 'a t +val ref: string Fmt.t +val url: string Fmt.t +val footnote: string Fmt.t + +val emph: 'a t +val bold: 'a t +val subscript: 'a t +val superscript: 'a t + +val section: 'a t +val subsection: 'a t +val subsubsection: 'a t +val paragraph: 'a t + +val enumerate: 'a t +val itemize: 'a t +val description: ('a, ('a * 'a) list) tr +val item: 'a t with_options + +val small_table: ('a, 'a list list) tr + + +val input: Fpath.t Fmt.t + +(** {1 Required OCaml-specific primitives } + All the macro should be implemented as "ocaml"-suffixed macro + in the latex preamble + *) + +(** {2 Code block customization} *) +val inline_code: 'a t +val code_fragment: 'a t +val code_block: 'a t + +(** {2 Package-dependent primitives }*) + +val indent: 'a t +(** expected to be implemented with changepage/adjustwidth*) + +val longtable: column_desc:pr -> 'a t +(** any table implementation that can be split on multiple pages, e.g. longtable*) + + +(** {2 Tags } *) + +val ocamltag: string -> 'a t +(** tag (e.g keyword, type-var, ...) are rendered to +{v \ocamltag{tagname}{content} v} +*) diff --git a/src/latex/types.ml b/src/latex/types.ml new file mode 100644 index 0000000000..bcf230972c --- /dev/null +++ b/src/latex/types.ml @@ -0,0 +1,42 @@ + +type break_hierarchy = + | Aesthetic + | Simple + | Line + | Paragraph + | Separation + + +type row_size = + | Empty + | Small (** text only *) + | Large (** No table *) + | Huge (** tables **) + +type elt = + | Txt of string list + | Section of section + | Verbatim of string + | Internal_ref of reference + | External_ref of string * t option + | Label of string + | Raw of string + | Tag of string * t + | Style of [`Emphasis|`Bold|`Superscript|`Subscript|`Italic] * t + | Code_block of t + | Inlined_code of t + | Code_fragment of t + | Break of break_hierarchy + | List of list_info + | Description of (t * t) list + | Indented of t + | Table of table + | Ligaturable of string + +and section = {level:int; label:string option; content:t } +and list_info = { typ : Odoc_document.Types.Block.list_type; items: t list } +and table = { row_size: row_size; tbl: t list list} + + +and t = elt list +and reference = { short:bool; target:string; text: t option } diff --git a/test/latex/expect/test_package+ml/Alias.X.tex b/test/latex/expect/test_package+ml/Alias.X.tex index 82e97d9d67..f62070a314 100644 --- a/test/latex/expect/test_package+ml/Alias.X.tex +++ b/test/latex/expect/test_package+ml/Alias.X.tex @@ -1,6 +1,5 @@ -\section{Module \inlinecode{Alias.\allowbreak{}X}}\label{package-test+u+package+++ml-module-Alias-module-X}% -\label{package-test+u+package+++ml-module-Alias-module-X-type-t}\codefragment{\begin{keyword}type\end{keyword} - 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{package-test+u+package+++ml-module-Alias-module-X}% +\label{package-test+u+package+++ml-module-Alias-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/Alias.tex b/test/latex/expect/test_package+ml/Alias.tex index bdc699af31..824ee206bc 100644 --- a/test/latex/expect/test_package+ml/Alias.tex +++ b/test/latex/expect/test_package+ml/Alias.tex @@ -1,15 +1,8 @@ -\section{Module \inlinecode{Alias}}\label{package-test+u+package+++ml-module-Alias}% -\label{package-test+u+package+++ml-module-Alias-module-Foo+u++u+X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Alias-module-Foo+u++u+X]{\inlinecode{Foo\_\allowbreak{}\_\allowbreak{}X}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Alias-module-Foo+u++u+X-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = \hyperref[xref-unresolved]{\inlinecode{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}}\label{package-test+u+package+++ml-module-Alias}% +\label{package-test+u+package+++ml-module-Alias-module-Foo+u++u+X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Alias-module-Foo+u++u+X]{\ocamlinlinecode{Foo\_\allowbreak{}\_\allowbreak{}X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Alias-module-Foo+u++u+X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[xref-unresolved]{\ocamlinlinecode{int}}}\begin{ocamlindent}Module Foo\_\_X documentation. This should appear in the documentation for the alias to this module 'X'\end{ocamlindent}% \medbreak \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Alias-module-X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Alias-module-X]{\inlinecode{X}}}\codefragment{ : \begin{keyword}sig\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Alias-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Alias-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{test_package+ml/Alias.X.tex} diff --git a/test/latex/expect/test_package+ml/Bugs.tex b/test/latex/expect/test_package+ml/Bugs.tex index e3bd1e9f9f..379420d362 100644 --- a/test/latex/expect/test_package+ml/Bugs.tex +++ b/test/latex/expect/test_package+ml/Bugs.tex @@ -1,10 +1,6 @@ -\section{Module \inlinecode{Bugs}}\label{package-test+u+package+++ml-module-Bugs}% -\label{package-test+u+package+++ml-module-Bugs-type-opt}\codefragment{\begin{keyword}type\end{keyword} - 'a opt = \begin{type-var}'a\end{type-var} - option}\\ -\label{package-test+u+package+++ml-module-Bugs-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : ?bar:\begin{type-var}'a\end{type-var} - $\rightarrow$ unit $\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{package-test+u+package+++ml-module-Bugs}% +\label{package-test+u+package+++ml-module-Bugs-type-opt}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt = \ocamltag{type-var}{'a} option}\\ +\label{package-test+u+package+++ml-module-Bugs-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : ?bar:\ocamltag{type-var}{'a} $\rightarrow$ unit $\rightarrow$ unit}\begin{ocamlindent}Triggers an assertion failure when \href{https://github.com/ocaml/odoc/issues/101}{https://github.com/ocaml/odoc/issues/101}\footnote{\url{https://github.com/ocaml/odoc/issues/101}} is not fixed.\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/Bugs_pre_410.tex b/test/latex/expect/test_package+ml/Bugs_pre_410.tex index 392bd2923d..957657ddf6 100644 --- a/test/latex/expect/test_package+ml/Bugs_pre_410.tex +++ b/test/latex/expect/test_package+ml/Bugs_pre_410.tex @@ -1,9 +1,6 @@ -\section{Module \inlinecode{Bugs\_\allowbreak{}pre\_\allowbreak{}410}}\label{package-test+u+package+++ml-module-Bugs+u+pre+u+410}% -\label{package-test+u+package+++ml-module-Bugs+u+pre+u+410-type-opt'}\codefragment{\begin{keyword}type\end{keyword} - 'a opt' = int option}\\ -\label{package-test+u+package+++ml-module-Bugs+u+pre+u+410-val-foo'}\codefragment{\begin{keyword}val\end{keyword} - foo' : ?bar:\begin{type-var}'a\end{type-var} - $\rightarrow$ unit $\rightarrow$ unit}\begin{ocamlindent}Similar to \inlinecode{Bugs}, but the printed type of \inlinecode{\textasciitilde{}bar} should be \inlinecode{int}, not \inlinecode{'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{package-test+u+package+++ml-module-Bugs+u+pre+u+410}% +\label{package-test+u+package+++ml-module-Bugs+u+pre+u+410-type-opt'}\ocamlcodefragment{\ocamltag{keyword}{type} 'a opt' = int option}\\ +\label{package-test+u+package+++ml-module-Bugs+u+pre+u+410-val-foo'}\ocamlcodefragment{\ocamltag{keyword}{val} foo' : ?bar:\ocamltag{type-var}{'a} $\rightarrow$ unit $\rightarrow$ unit}\begin{ocamlindent}Similar to \ocamlinlinecode{Bugs}, but the printed type of \ocamlinlinecode{\textasciitilde{}bar} should be \ocamlinlinecode{int}, not \ocamlinlinecode{'a}. This probably requires fixing in the compiler. See \href{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}\footnote{\url{https://github.com/ocaml/odoc/pull/230\#issuecomment-433226807}}.\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/Class.empty_virtual'.tex b/test/latex/expect/test_package+ml/Class.empty_virtual'.tex index 8e32a5f14c..c4b6dcf937 100644 --- a/test/latex/expect/test_package+ml/Class.empty_virtual'.tex +++ b/test/latex/expect/test_package+ml/Class.empty_virtual'.tex @@ -1,3 +1,3 @@ -\section{Class \inlinecode{Class.\allowbreak{}empty\_\allowbreak{}virtual'}}\label{package-test+u+package+++ml-module-Class-class-empty+u+virtual'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}empty\_\allowbreak{}virtual'}}\label{package-test+u+package+++ml-module-Class-class-empty+u+virtual'}% diff --git a/test/latex/expect/test_package+ml/Class.mutually'.tex b/test/latex/expect/test_package+ml/Class.mutually'.tex index 08af432ed5..82792c2704 100644 --- a/test/latex/expect/test_package+ml/Class.mutually'.tex +++ b/test/latex/expect/test_package+ml/Class.mutually'.tex @@ -1,3 +1,3 @@ -\section{Class \inlinecode{Class.\allowbreak{}mutually'}}\label{package-test+u+package+++ml-module-Class-class-mutually'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}mutually'}}\label{package-test+u+package+++ml-module-Class-class-mutually'}% diff --git a/test/latex/expect/test_package+ml/Class.polymorphic'.tex b/test/latex/expect/test_package+ml/Class.polymorphic'.tex index af3f51f652..a470185953 100644 --- a/test/latex/expect/test_package+ml/Class.polymorphic'.tex +++ b/test/latex/expect/test_package+ml/Class.polymorphic'.tex @@ -1,3 +1,3 @@ -\section{Class \inlinecode{Class.\allowbreak{}polymorphic'}}\label{package-test+u+package+++ml-module-Class-class-polymorphic'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}polymorphic'}}\label{package-test+u+package+++ml-module-Class-class-polymorphic'}% diff --git a/test/latex/expect/test_package+ml/Class.recursive'.tex b/test/latex/expect/test_package+ml/Class.recursive'.tex index b7ce10638c..395e5f9388 100644 --- a/test/latex/expect/test_package+ml/Class.recursive'.tex +++ b/test/latex/expect/test_package+ml/Class.recursive'.tex @@ -1,3 +1,3 @@ -\section{Class \inlinecode{Class.\allowbreak{}recursive'}}\label{package-test+u+package+++ml-module-Class-class-recursive'}% +\section{Class \ocamlinlinecode{Class.\allowbreak{}recursive'}}\label{package-test+u+package+++ml-module-Class-class-recursive'}% diff --git a/test/latex/expect/test_package+ml/Class.tex b/test/latex/expect/test_package+ml/Class.tex index 0201d49c0e..bec533dd3b 100644 --- a/test/latex/expect/test_package+ml/Class.tex +++ b/test/latex/expect/test_package+ml/Class.tex @@ -1,44 +1,18 @@ -\section{Module \inlinecode{Class}}\label{package-test+u+package+++ml-module-Class}% -\label{package-test+u+package+++ml-module-Class-class-type-empty}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-type-empty]{\inlinecode{empty}}}\codefragment{ = \begin{keyword}object\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Class-class-type-mutually}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-type-mutually]{\inlinecode{mutually}}}\codefragment{ = \begin{keyword}object\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Class-class-type-recursive}\codefragment{\begin{keyword}and\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-type-recursive]{\inlinecode{recursive}}}\codefragment{ = \begin{keyword}object\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Class-class-mutually'}\codefragment{\begin{keyword}class\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-mutually']{\inlinecode{mutually'}}}\codefragment{ : \hyperref[package-test+u+package+++ml-module-Class-class-type-mutually]{\inlinecode{mutually}}}\\ -\label{package-test+u+package+++ml-module-Class-class-recursive'}\codefragment{\begin{keyword}and\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-recursive']{\inlinecode{recursive'}}}\codefragment{ : \hyperref[package-test+u+package+++ml-module-Class-class-type-recursive]{\inlinecode{recursive}}}\\ -\label{package-test+u+package+++ml-module-Class-class-type-empty+u+virtual}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}type\end{keyword} - \begin{keyword}virtual\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-type-empty+u+virtual]{\inlinecode{empty\_\allowbreak{}virtual}}}\codefragment{ = \begin{keyword}object\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Class-class-empty+u+virtual'}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}virtual\end{keyword} - \hyperref[package-test+u+package+++ml-module-Class-class-empty+u+virtual']{\inlinecode{empty\_\allowbreak{}virtual'}}}\codefragment{ : \hyperref[package-test+u+package+++ml-module-Class-class-type-empty]{\inlinecode{empty}}}\\ -\label{package-test+u+package+++ml-module-Class-class-type-polymorphic}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}type\end{keyword} - 'a \hyperref[package-test+u+package+++ml-module-Class-class-type-polymorphic]{\inlinecode{polymorphic}}}\codefragment{ = \begin{keyword}object\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Class-class-polymorphic'}\codefragment{\begin{keyword}class\end{keyword} - 'a \hyperref[package-test+u+package+++ml-module-Class-class-polymorphic']{\inlinecode{polymorphic'}}}\codefragment{ : \begin{type-var}'a\end{type-var} - \hyperref[package-test+u+package+++ml-module-Class-class-type-polymorphic]{\inlinecode{polymorphic}}}\\ +\section{Module \ocamlinlinecode{Class}}\label{package-test+u+package+++ml-module-Class}% +\label{package-test+u+package+++ml-module-Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{and} \hyperref[package-test+u+package+++ml-module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[package-test+u+package+++ml-module-Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[package-test+u+package+++ml-module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\ +\label{package-test+u+package+++ml-module-Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{and} \hyperref[package-test+u+package+++ml-module-Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[package-test+u+package+++ml-module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\ +\label{package-test+u+package+++ml-module-Class-class-type-empty+u+virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[package-test+u+package+++ml-module-Class-class-type-empty+u+virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Class-class-empty+u+virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[package-test+u+package+++ml-module-Class-class-empty+u+virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[package-test+u+package+++ml-module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\\ +\label{package-test+u+package+++ml-module-Class-class-type-polymorphic}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} 'a \hyperref[package-test+u+package+++ml-module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Class-class-polymorphic'}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[package-test+u+package+++ml-module-Class-class-polymorphic']{\ocamlinlinecode{polymorphic'}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \hyperref[package-test+u+package+++ml-module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\\ \input{test_package+ml/Class.mutually'.tex} \input{test_package+ml/Class.recursive'.tex} diff --git a/test/latex/expect/test_package+ml/External.tex b/test/latex/expect/test_package+ml/External.tex index eac85e4a47..0f9e791f31 100644 --- a/test/latex/expect/test_package+ml/External.tex +++ b/test/latex/expect/test_package+ml/External.tex @@ -1,6 +1,5 @@ -\section{Module \inlinecode{External}}\label{package-test+u+package+++ml-module-External}% -\label{package-test+u+package+++ml-module-External-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit $\rightarrow$ unit}\begin{ocamlindent}Foo \emph{bar}.\end{ocamlindent}% +\section{Module \ocamlinlinecode{External}}\label{package-test+u+package+++ml-module-External}% +\label{package-test+u+package+++ml-module-External-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit $\rightarrow$ unit}\begin{ocamlindent}Foo \emph{bar}.\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/Functor.F1.tex b/test/latex/expect/test_package+ml/Functor.F1.tex index b4623354ae..73459864f9 100644 --- a/test/latex/expect/test_package+ml/Functor.F1.tex +++ b/test/latex/expect/test_package+ml/Functor.F1.tex @@ -1,14 +1,9 @@ -\section{Module \inlinecode{Functor.\allowbreak{}F1}}\label{package-test+u+package+++ml-module-Functor-module-F1}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F1}}\label{package-test+u+package+++ml-module-Functor-module-F1}% \subsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg]{\inlinecode{Arg}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Functor-module-F1-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/latex/expect/test_package+ml/Functor.F2.tex b/test/latex/expect/test_package+ml/Functor.F2.tex index 4eba604937..4dc3154f10 100644 --- a/test/latex/expect/test_package+ml/Functor.F2.tex +++ b/test/latex/expect/test_package+ml/Functor.F2.tex @@ -1,14 +1,9 @@ -\section{Module \inlinecode{Functor.\allowbreak{}F2}}\label{package-test+u+package+++ml-module-Functor-module-F2}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F2}}\label{package-test+u+package+++ml-module-Functor-module-F2}% \subsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg]{\inlinecode{Arg}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Functor-module-F2-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = \hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t]{\inlinecode{Arg.\allowbreak{}t}}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ diff --git a/test/latex/expect/test_package+ml/Functor.F3.tex b/test/latex/expect/test_package+ml/Functor.F3.tex index 7b73288fd0..e0f550abca 100644 --- a/test/latex/expect/test_package+ml/Functor.F3.tex +++ b/test/latex/expect/test_package+ml/Functor.F3.tex @@ -1,14 +1,9 @@ -\section{Module \inlinecode{Functor.\allowbreak{}F3}}\label{package-test+u+package+++ml-module-Functor-module-F3}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F3}}\label{package-test+u+package+++ml-module-Functor-module-F3}% \subsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg]{\inlinecode{Arg}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Functor-module-F3-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = \hyperref[package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg-type-t]{\inlinecode{Arg.\allowbreak{}t}}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ diff --git a/test/latex/expect/test_package+ml/Functor.F4.tex b/test/latex/expect/test_package+ml/Functor.F4.tex index 80b7ed3906..ff32b515ff 100644 --- a/test/latex/expect/test_package+ml/Functor.F4.tex +++ b/test/latex/expect/test_package+ml/Functor.F4.tex @@ -1,14 +1,9 @@ -\section{Module \inlinecode{Functor.\allowbreak{}F4}}\label{package-test+u+package+++ml-module-Functor-module-F4}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F4}}\label{package-test+u+package+++ml-module-Functor-module-F4}% \subsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg]{\inlinecode{Arg}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Functor-module-F4-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F4-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/latex/expect/test_package+ml/Functor.F5.tex b/test/latex/expect/test_package+ml/Functor.F5.tex index 46389fdf73..54dd46e75e 100644 --- a/test/latex/expect/test_package+ml/Functor.F5.tex +++ b/test/latex/expect/test_package+ml/Functor.F5.tex @@ -1,7 +1,6 @@ -\section{Module \inlinecode{Functor.\allowbreak{}F5}}\label{package-test+u+package+++ml-module-Functor-module-F5}% +\section{Module \ocamlinlinecode{Functor.\allowbreak{}F5}}\label{package-test+u+package+++ml-module-Functor-module-F5}% \subsection{Parameters\label{parameters}}% \subsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Functor-module-F5-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-F5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ diff --git a/test/latex/expect/test_package+ml/Functor.tex b/test/latex/expect/test_package+ml/Functor.tex index 3210cad7ee..51f06a0a31 100644 --- a/test/latex/expect/test_package+ml/Functor.tex +++ b/test/latex/expect/test_package+ml/Functor.tex @@ -1,43 +1,20 @@ -\section{Module \inlinecode{Functor}}\label{package-test+u+package+++ml-module-Functor}% -\label{package-test+u+package+++ml-module-Functor-module-type-S}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-type-S-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\section{Module \ocamlinlinecode{Functor}}\label{package-test+u+package+++ml-module-Functor}% +\label{package-test+u+package+++ml-module-Functor-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Functor-module-type-S1}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-type-S1]{\inlinecode{S1}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+]{\inlinecode{\_\allowbreak{}}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Functor-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Functor-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{package-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Functor-module-type-S1-argument-1-+u+-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Functor-module-type-S1-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Functor-module-type-S1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Functor-module-F1}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F1]{\inlinecode{F1}}}\codefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg]{\inlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}) : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}}\\ -\label{package-test+u+package+++ml-module-Functor-module-F2}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F2]{\inlinecode{F2}}}\codefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg]{\inlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}) : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}} \begin{keyword}with\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-type-S-type-t]{\inlinecode{t}} = \hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t]{\inlinecode{Arg.\allowbreak{}t}}}\\ -\label{package-test+u+package+++ml-module-Functor-module-F3}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F3]{\inlinecode{F3}}}\codefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg]{\inlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}) : \begin{keyword}sig\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Functor-module-F4}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F4]{\inlinecode{F4}}}\codefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg]{\inlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}) : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}}\\ -\label{package-test+u+package+++ml-module-Functor-module-F5}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Functor-module-F5]{\inlinecode{F5}}}\codefragment{ () : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\inlinecode{S}}}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F1]{\ocamlinlinecode{F1}}}\ocamlcodefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F1-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F2]{\ocamlinlinecode{F2}}}\ocamlcodefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Functor-module-type-S-type-t]{\ocamlinlinecode{t}} = \hyperref[package-test+u+package+++ml-module-Functor-module-F2-argument-1-Arg-type-t]{\ocamlinlinecode{Arg.\allowbreak{}t}}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F3}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F3]{\ocamlinlinecode{F3}}}\ocamlcodefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F3-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F4}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F4]{\ocamlinlinecode{F4}}}\ocamlcodefragment{ (\hyperref[package-test+u+package+++ml-module-Functor-module-F4-argument-1-Arg]{\ocamlinlinecode{Arg}} : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}) : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\ +\label{package-test+u+package+++ml-module-Functor-module-F5}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Functor-module-F5]{\ocamlinlinecode{F5}}}\ocamlcodefragment{ () : \hyperref[package-test+u+package+++ml-module-Functor-module-type-S]{\ocamlinlinecode{S}}}\\ \input{test_package+ml/Functor.F1.tex} \input{test_package+ml/Functor.F2.tex} diff --git a/test/latex/expect/test_package+ml/Include.tex b/test/latex/expect/test_package+ml/Include.tex index 66596212a9..1845ebb32c 100644 --- a/test/latex/expect/test_package+ml/Include.tex +++ b/test/latex/expect/test_package+ml/Include.tex @@ -1,47 +1,19 @@ -\section{Module \inlinecode{Include}}\label{package-test+u+package+++ml-module-Include}% -\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined]{\inlinecode{Not\_\allowbreak{}inlined}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\section{Module \ocamlinlinecode{Include}}\label{package-test+u+package+++ml-module-Include}% +\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined]{\inlinecode{Not\_\allowbreak{}inlined}}\label{package-test+u+package+++ml-module-Include-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Include-module-type-Inlined}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Inlined]{\inlinecode{Inlined}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Inlined-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined]{\ocamlinlinecode{Not\_\allowbreak{}inlined}}\label{package-test+u+package+++ml-module-Include-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Include-module-type-Inlined}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Inlined-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Inlined]{\inlinecode{Inlined}}\label{package-test+u+package+++ml-module-Include-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\inlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed-type-v}\codefragment{\begin{keyword}type\end{keyword} - v}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include-module-type-Inlined]{\ocamlinlinecode{Inlined}}\label{package-test+u+package+++ml-module-Include-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\inlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}\label{package-test+u+package+++ml-module-Include-type-v}\codefragment{\begin{keyword}type\end{keyword} - v}\\ -\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\inlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened-type-w}\codefragment{\begin{keyword}type\end{keyword} - w}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+closed]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}closed}}\label{package-test+u+package+++ml-module-Include-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v}\\ +\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\inlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}\label{package-test+u+package+++ml-module-Include-type-w}\codefragment{\begin{keyword}type\end{keyword} - w}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include-module-type-Not+u+inlined+u+and+u+opened]{\ocamlinlinecode{Not\_\allowbreak{}inlined\_\allowbreak{}and\_\allowbreak{}opened}}\label{package-test+u+package+++ml-module-Include-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} w}\\ diff --git a/test/latex/expect/test_package+ml/Include2.tex b/test/latex/expect/test_package+ml/Include2.tex index 7fc5854dd0..f425893735 100644 --- a/test/latex/expect/test_package+ml/Include2.tex +++ b/test/latex/expect/test_package+ml/Include2.tex @@ -1,14 +1,8 @@ -\section{Module \inlinecode{Include2}}\label{package-test+u+package+++ml-module-Include2}% -\label{package-test+u+package+++ml-module-Include2-module-X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include2-module-X]{\inlinecode{X}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include2-module-X-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = int}\\ +\section{Module \ocamlinlinecode{Include2}}\label{package-test+u+package+++ml-module-Include2}% +\label{package-test+u+package+++ml-module-Include2-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Include2-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include2-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\begin{ocamlindent}Comment about X that should not appear when including X below.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Comment about X that should not appear when including X below.\end{ocamlindent}% \medbreak -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include2-module-X]{\inlinecode{X}}\label{package-test+u+package+++ml-module-Include2-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = int}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include2-module-X]{\ocamlinlinecode{X}}\label{package-test+u+package+++ml-module-Include2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ diff --git a/test/latex/expect/test_package+ml/Include_sections.tex b/test/latex/expect/test_package+ml/Include_sections.tex index b4e29b6ec0..d5896ad643 100644 --- a/test/latex/expect/test_package+ml/Include_sections.tex +++ b/test/latex/expect/test_package+ml/Include_sections.tex @@ -1,56 +1,41 @@ -\section{Module \inlinecode{Include\_\allowbreak{}sections}}\label{package-test+u+package+++ml-module-Include+u+sections}% -\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{Something}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-something}\codefragment{\begin{keyword}val\end{keyword} - something : unit}\\ +\section{Module \ocamlinlinecode{Include\_\allowbreak{}sections}}\label{package-test+u+package+++ml-module-Include+u+sections}% +\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsubsection{Something 1\label{something-1}}% foo -\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\\ +\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2}}% -\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-bar}\codefragment{\begin{keyword}val\end{keyword} - bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Include+u+sections-module-type-Something-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsubsection{Something 1-bis\label{something-1-bis}}% Some text. \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\begin{ocamlindent}A module type.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}A module type.\end{ocamlindent}% \medbreak -Let's include \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{\inlinecode{Something}}[p\pageref*{package-test+u+package+++ml-module-Include+u+sections-module-type-Something}]} once +Let's include \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{package-test+u+package+++ml-module-Include+u+sections-module-type-Something}]} once -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\codefragment{\begin{keyword}val\end{keyword} - something : unit}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsection{Something 1\label{something-1}}% foo -\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\\ +\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2}}% -\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\codefragment{\begin{keyword}val\end{keyword} - bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsection{Something 1-bis\label{something-1-bis}}% Some text. \subsection{Second include\label{second-include}}% -Let's include \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{\inlinecode{Something}}[p\pageref*{package-test+u+package+++ml-module-Include+u+sections-module-type-Something}]} a second time: the heading level should be shift here. +Let's include \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{\ocamlinlinecode{Something}}[p\pageref*{package-test+u+package+++ml-module-Include+u+sections-module-type-Something}]} a second time: the heading level should be shift here. -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\codefragment{\begin{keyword}val\end{keyword} - something : unit}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsection{Something 1\label{something-1}}% foo -\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\\ +\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2}}% -\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\codefragment{\begin{keyword}val\end{keyword} - bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsection{Something 1-bis\label{something-1-bis}}% Some text. @@ -58,34 +43,26 @@ \subsection{Something 1-bis\label{something-1-bis}}% \subsubsection{Third include\label{third-include}}% Shifted some more. -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\codefragment{\begin{keyword}val\end{keyword} - something : unit}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsection{Something 1\label{something-1}}% foo -\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\\ +\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2}}% -\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\codefragment{\begin{keyword}val\end{keyword} - bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsection{Something 1-bis\label{something-1-bis}}% Some text. And let's include it again, but without inlining it this time: the ToC shouldn't grow. -\begin{keyword}include\end{keyword} - \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\inlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\codefragment{\begin{keyword}val\end{keyword} - something : unit}\\ +\ocamltag{keyword}{include} \hyperref[package-test+u+package+++ml-module-Include+u+sections-module-type-Something]{\ocamlinlinecode{Something}}\label{package-test+u+package+++ml-module-Include+u+sections-val-something}\ocamlcodefragment{\ocamltag{keyword}{val} something : unit}\\ \subsection{Something 1\label{something-1}}% foo -\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\\ +\label{package-test+u+package+++ml-module-Include+u+sections-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsubsection{Something 2\label{something-2}}% -\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\codefragment{\begin{keyword}val\end{keyword} - bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Include+u+sections-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}foo bar\end{ocamlindent}% \medbreak \subsection{Something 1-bis\label{something-1-bis}}% Some text. diff --git a/test/latex/expect/test_package+ml/Interlude.tex b/test/latex/expect/test_package+ml/Interlude.tex index beea240b5a..fd8164fc1f 100644 --- a/test/latex/expect/test_package+ml/Interlude.tex +++ b/test/latex/expect/test_package+ml/Interlude.tex @@ -1,10 +1,9 @@ -\section{Module \inlinecode{Interlude}}\label{package-test+u+package+++ml-module-Interlude}% +\section{Module \ocamlinlinecode{Interlude}}\label{package-test+u+package+++ml-module-Interlude}% This is the comment associated to the module. Some separate stray text at the top of the module. -\label{package-test+u+package+++ml-module-Interlude-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Interlude-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% \medbreak Some stray text that is not associated with any signature item. @@ -12,15 +11,11 @@ \section{Module \inlinecode{Interlude}}\label{package-test+u+package+++ml-module A separate block of stray text, adjacent to the preceding one. -\label{package-test+u+package+++ml-module-Interlude-val-bar}\codefragment{\begin{keyword}val\end{keyword} - bar : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Interlude-val-bar}\ocamlcodefragment{\ocamltag{keyword}{val} bar : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% \medbreak -\label{package-test+u+package+++ml-module-Interlude-val-multiple}\codefragment{\begin{keyword}val\end{keyword} - multiple : unit}\\ -\label{package-test+u+package+++ml-module-Interlude-val-signature}\codefragment{\begin{keyword}val\end{keyword} - signature : unit}\\ -\label{package-test+u+package+++ml-module-Interlude-val-items}\codefragment{\begin{keyword}val\end{keyword} - items : unit}\\ +\label{package-test+u+package+++ml-module-Interlude-val-multiple}\ocamlcodefragment{\ocamltag{keyword}{val} multiple : unit}\\ +\label{package-test+u+package+++ml-module-Interlude-val-signature}\ocamlcodefragment{\ocamltag{keyword}{val} signature : unit}\\ +\label{package-test+u+package+++ml-module-Interlude-val-items}\ocamlcodefragment{\ocamltag{keyword}{val} items : unit}\\ Stray text at the bottom of the module. diff --git a/test/latex/expect/test_package+ml/Markup.tex b/test/latex/expect/test_package+ml/Markup.tex index 665481e8de..6e74a5484f 100644 --- a/test/latex/expect/test_package+ml/Markup.tex +++ b/test/latex/expect/test_package+ml/Markup.tex @@ -1,4 +1,4 @@ -\section{Module \inlinecode{Markup}}\label{package-test+u+package+++ml-module-Markup}% +\section{Module \ocamlinlinecode{Markup}}\label{package-test+u+package+++ml-module-Markup}% Here, we test the rendering of comment markup. \subsection{Sections\label{sections}}% @@ -13,7 +13,7 @@ \subsubsection{Sub-subsection headings\label{sub-subsection-headings}}% but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. \subsubsection{Anchors\label{anchors}}% -Sections can have attached \hyperref[package-test+u+package+++ml-module-Markup-anchors]{\inlinecode{Anchors}[p\pageref*{package-test+u+package+++ml-module-Markup-anchors}]}, and it is possible to \hyperref[package-test+u+package+++ml-module-Markup-anchors]{\inlinecode{link}[p\pageref*{package-test+u+package+++ml-module-Markup-anchors}]} to them. Links to section headers should not be set in source code style. +Sections can have attached \hyperref[package-test+u+package+++ml-module-Markup-anchors]{\ocamlinlinecode{Anchors}[p\pageref*{package-test+u+package+++ml-module-Markup-anchors}]}, and it is possible to \hyperref[package-test+u+package+++ml-module-Markup-anchors]{\ocamlinlinecode{link}[p\pageref*{package-test+u+package+++ml-module-Markup-anchors}]} to them. Links to section headers should not be set in source code style. \subsubsection{Paragraph\label{paragraph}}% Individual paragraphs can have a heading. @@ -22,22 +22,22 @@ \subsubsection{Subparagraph\label{subparagraph}}% Parts of a longer paragraph that can be considered alone can also have headings. \subsection{Styling\label{styling}}% -This paragraph has some styled elements: \textbf{bold} and \emph{italic}, \textbf{\emph{bold italic}}, \emph{emphasis}, \emph{\emph{emphasis} within emphasis}, \textbf{\emph{bold italic}}, super\textsuperscript{script}, sub\textsubscript{script}. The line spacing should be enough for superscripts and subscripts not to look odd. +This paragraph has some styled elements: \bold{bold} and \emph{italic}, \bold{\emph{bold italic}}, \emph{emphasis}, \emph{\emph{emphasis} within emphasis}, \bold{\emph{bold italic}}, super\textsuperscript{script}, sub\textsubscript{script}. The line spacing should be enough for superscripts and subscripts not to look odd. Note: \emph{In italics \emph{emphasis} is rendered as normal text while \emph{emphasis \emph{in} emphasis} is rendered in italics.} \emph{It also work the same in \href{\#}{links in italics with \emph{emphasis \emph{in} emphasis}.}\footnote{\url{\#}}} -\inlinecode{code} is a different kind of markup that doesn't allow nested markup. +\ocamlinlinecode{code} is a different kind of markup that doesn't allow nested markup. -It's possible for two markup elements to appear \textbf{next} \emph{to} each other and have a space, and appear \textbf{next}\emph{to} each other with no space. It doesn't matter \textbf{how} \emph{much} space it was in the source: in this sentence, it was two space characters. And in this one, there is \textbf{a} \emph{newline}. +It's possible for two markup elements to appear \bold{next} \emph{to} each other and have a space, and appear \bold{next}\emph{to} each other with no space. It doesn't matter \bold{how} \emph{much} space it was in the source: in this sentence, it was two space characters. And in this one, there is \bold{a} \emph{newline}. -This is also true between \emph{non-}\inlinecode{code} markup \emph{and} \inlinecode{code}. +This is also true between \emph{non-}\ocamlinlinecode{code} markup \emph{and} \ocamlinlinecode{code}. -Code can appear \textbf{inside \inlinecode{other} markup}. Its display shouldn't be affected. +Code can appear \bold{inside \ocamlinlinecode{other} markup}. Its display shouldn't be affected. \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{\#}{\textbf{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{\#}{\inlinecode{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 \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[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\inlinecode{foo}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}. References can have replacement text: \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{the value foo}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}. Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\textbf{bold}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\emph{italic}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\emph{emphasis}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{super\textsuperscript{script}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{sub\textsubscript{script}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, and \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\inlinecode{code}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}. It's also possible to surround a reference in a style: \textbf{\hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\inlinecode{foo}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}}. References can't be nested inside references, and links and references can't be nested inside each other. +This is a reference to \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}. References can have replacement text: \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{the value foo}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}. Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\bold{bold}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\emph{italic}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\emph{emphasis}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{super\textsuperscript{script}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{sub\textsubscript{script}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}, and \hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{code}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}. It's also possible to surround a reference in a style: \bold{\hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}}. References can't be nested inside references, and links and references can't be nested inside each other. \subsection{Preformatted text\label{preformatted-text}}% This is a code block:\medbreak @@ -74,7 +74,7 @@ \subsection{Lists\label{lists}}% \begin{itemize}\item{\begin{itemize}\item{lists}% \item{can be nested}% \item{and can include references}% -\item{\hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\inlinecode{\inlinecode{foo}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}}\end{itemize}% +\item{\hyperref[package-test+u+package+++ml-module-Markup-val-foo]{\ocamlinlinecode{\ocamlinlinecode{foo}}[p\pageref*{package-test+u+package+++ml-module-Markup-val-foo}]}}\end{itemize}% }\end{itemize}% \subsection{Unicode\label{unicode}}% The parser supports any ASCII-compatible encoding, in particuλar UTF-8. @@ -83,10 +83,10 @@ \subsection{Raw HTML\label{raw-html}}% Raw HTML can be as inline elements into sentences. \subsection{Modules\label{modules}}% -\begin{itemize}\item{\inlinecode{X}}\end{itemize}% -\begin{itemize}\item{\inlinecode{X}}% -\item{\inlinecode{Y}}% -\item{\inlinecode{Z}}\end{itemize}% +\begin{itemize}\item{\ocamlinlinecode{X}}\end{itemize}% +\begin{itemize}\item{\ocamlinlinecode{X}}% +\item{\ocamlinlinecode{Y}}% +\item{\ocamlinlinecode{Z}}\end{itemize}% \subsection{Tags\label{tags}}% Each comment can end with zero or more tags. Here are some examples: @@ -120,7 +120,7 @@ \subsection{Tags\label{tags}}% }\end{description}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded -\item[see \inlinecode{foo.\allowbreak{}ml}]{this file +\item[see \ocamlinlinecode{foo.\allowbreak{}ml}]{this file }\end{description}% \begin{description}\kern-\topsep @@ -139,8 +139,7 @@ \subsection{Tags\label{tags}}% \begin{description}\kern-\topsep \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded \item[version]{-1}\end{description}% -\label{package-test+u+package+++ml-module-Markup-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\begin{ocamlindent}Comments in structure items \textbf{support} \emph{markup}, t\textsuperscript{o}\textsubscript{o}.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Markup-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}Comments in structure items \bold{support} \emph{markup}, t\textsuperscript{o}\textsubscript{o}.\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/Module.tex b/test/latex/expect/test_package+ml/Module.tex index ce7ba8494e..b2a0c947cf 100644 --- a/test/latex/expect/test_package+ml/Module.tex +++ b/test/latex/expect/test_package+ml/Module.tex @@ -1,173 +1,75 @@ -\section{Module \inlinecode{Module}}\label{package-test+u+package+++ml-module-Module}% +\section{Module \ocamlinlinecode{Module}}\label{package-test+u+package+++ml-module-Module}% Foo. -\label{package-test+u+package+++ml-module-Module-val-foo}\codefragment{\begin{keyword}val\end{keyword} - 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{package-test+u+package+++ml-module-Module-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\begin{ocamlindent}The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See \href{https://caml.inria.fr/mantis/view.php?id=7701}{https://caml.inria.fr/mantis/view.php?id=7701}\footnote{\url{https://caml.inria.fr/mantis/view.php?id=7701}}.\end{ocamlindent}% \medbreak -\label{package-test+u+package+++ml-module-Module-module-type-S}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S]{\inlinecode{S}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S-module-M}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S-module-M]{\inlinecode{M}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-type-S-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S1}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - S1}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S2}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S2]{\inlinecode{S2}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S2-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S2-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S2-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S2-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S2-module-M}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S2-module-M]{\inlinecode{M}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} S1}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S2}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S2]{\ocamlinlinecode{S2}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S2-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S2-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S2-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S2-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-type-S2-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S3}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S3]{\inlinecode{S3}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S3-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = int}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S3-type-u}\codefragment{\begin{keyword}type\end{keyword} - u = string}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S3-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S3-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S3-module-M}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S3-module-M]{\inlinecode{M}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S3}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S3]{\ocamlinlinecode{S3}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S3-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S3-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u = string}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S3-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S3-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S3-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-type-S3-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S4}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S4]{\inlinecode{S4}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S4-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S4-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S4-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S4-module-M}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S4-module-M]{\inlinecode{M}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S4}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S4]{\ocamlinlinecode{S4}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S4-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S4-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S4-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S4-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-type-S4-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S5}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S5]{\inlinecode{S5}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S5-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S5-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S5-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S5-module-M}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S5-module-M]{\inlinecode{M}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S5}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S5]{\ocamlinlinecode{S5}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S5-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S5-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S5-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S5-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-type-S5-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-type-result}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) result}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S6}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S6]{\inlinecode{S6}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S6-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S6-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S6-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S6-module-M}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S6-module-M]{\inlinecode{M}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-type-result}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) result}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S6}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S6]{\ocamlinlinecode{S6}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S6-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S6-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S6-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S6-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-type-S6-module-M]{\ocamlinlinecode{M}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-M'}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-M']{\inlinecode{M'}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S7}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S7]{\inlinecode{S7}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S7-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S7-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S7-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S7-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S7-module-M}\codefragment{\begin{keyword}module\end{keyword} - M = \hyperref[package-test+u+package+++ml-module-Module-module-M']{\inlinecode{M'}}}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-M'}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Module-module-M']{\ocamlinlinecode{M'}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S7}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S7]{\ocamlinlinecode{S7}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S7-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S7-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S7-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S7-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S7-module-M}\ocamlcodefragment{\ocamltag{keyword}{module} M = \hyperref[package-test+u+package+++ml-module-Module-module-M']{\ocamlinlinecode{M'}}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S8}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S8]{\inlinecode{S8}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S8-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S8-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S8-type-v}\codefragment{\begin{keyword}type\end{keyword} - 'a v}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S8-type-w}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) w}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S8}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S8]{\ocamlinlinecode{S8}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Module-module-type-S8-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S8-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S8-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} 'a v}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S8-type-w}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) w}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-type-S9}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-type-S9]{\inlinecode{S9}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-Mutually}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}rec\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-Mutually]{\inlinecode{Mutually}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Module-module-Recursive}\codefragment{\begin{keyword}and\end{keyword} - \hyperref[package-test+u+package+++ml-module-Module-module-Recursive]{\inlinecode{Recursive}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-type-S9}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Module-module-type-S9]{\ocamlinlinecode{S9}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-Mutually}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{rec} \hyperref[package-test+u+package+++ml-module-Module-module-Mutually]{\ocamlinlinecode{Mutually}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Module-module-Recursive}\ocamlcodefragment{\ocamltag{keyword}{and} \hyperref[package-test+u+package+++ml-module-Module-module-Recursive]{\ocamlinlinecode{Recursive}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/latex/expect/test_package+ml/Nested.F.tex b/test/latex/expect/test_package+ml/Nested.F.tex index 8369110313..2cf097dc30 100644 --- a/test/latex/expect/test_package+ml/Nested.F.tex +++ b/test/latex/expect/test_package+ml/Nested.F.tex @@ -1,35 +1,25 @@ -\section{Module \inlinecode{Nested.\allowbreak{}F}}\label{package-test+u+package+++ml-module-Nested-module-F}% +\section{Module \ocamlinlinecode{Nested.\allowbreak{}F}}\label{package-test+u+package+++ml-module-Nested-module-F}% This is a functor F. Some additional comments. \subsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1]{\inlinecode{Arg1}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Type\label{type}}% -\label{package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% +\label{package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \subsubsection{Values\label{values}}% -\label{package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-val-y}\codefragment{\begin{keyword}val\end{keyword} - y : \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t]{\inlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% \medbreak \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2]{\inlinecode{Arg2}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Type\label{type}}% -\label{package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% +\label{package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsection{Signature\label{signature}}% \subsection{Type\label{type}}% -\label{package-test+u+package+++ml-module-Nested-module-F-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t]{\inlinecode{Arg1.\allowbreak{}t}} * \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2-type-t]{\inlinecode{Arg2.\allowbreak{}t}}}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1-type-t]{\ocamlinlinecode{Arg1.\allowbreak{}t}} * \hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2-type-t]{\ocamlinlinecode{Arg2.\allowbreak{}t}}}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/Nested.inherits.tex b/test/latex/expect/test_package+ml/Nested.inherits.tex index 5dc1651c0b..a9d34121a5 100644 --- a/test/latex/expect/test_package+ml/Nested.inherits.tex +++ b/test/latex/expect/test_package+ml/Nested.inherits.tex @@ -1,5 +1,4 @@ -\section{Class \inlinecode{Nested.\allowbreak{}inherits}}\label{package-test+u+package+++ml-module-Nested-class-inherits}% -\codefragment{\begin{keyword}inherit\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-class-z]{\inlinecode{z}}}\\ +\section{Class \ocamlinlinecode{Nested.\allowbreak{}inherits}}\label{package-test+u+package+++ml-module-Nested-class-inherits}% +\ocamlcodefragment{\ocamltag{keyword}{inherit} \hyperref[package-test+u+package+++ml-module-Nested-class-z]{\ocamlinlinecode{z}}}\\ diff --git a/test/latex/expect/test_package+ml/Nested.tex b/test/latex/expect/test_package+ml/Nested.tex index 553be4b2fc..755ecb3b4c 100644 --- a/test/latex/expect/test_package+ml/Nested.tex +++ b/test/latex/expect/test_package+ml/Nested.tex @@ -1,57 +1,33 @@ -\section{Module \inlinecode{Nested}}\label{package-test+u+package+++ml-module-Nested}% +\section{Module \ocamlinlinecode{Nested}}\label{package-test+u+package+++ml-module-Nested}% This comment needs to be here before \#235 is fixed. \subsection{Module\label{module}}% -\label{package-test+u+package+++ml-module-Nested-module-X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-module-X]{\inlinecode{X}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Type\label{type}}% -\label{package-test+u+package+++ml-module-Nested-module-X-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Nested-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% +\label{package-test+u+package+++ml-module-Nested-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \subsubsection{Values\label{values}}% -\label{package-test+u+package+++ml-module-Nested-module-X-val-x}\codefragment{\begin{keyword}val\end{keyword} - x : \hyperref[package-test+u+package+++ml-module-Nested-module-X-type-t]{\inlinecode{t}}}\begin{ocamlindent}The value of x.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-X-val-x}\ocamlcodefragment{\ocamltag{keyword}{val} x : \hyperref[package-test+u+package+++ml-module-Nested-module-X-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of x.\end{ocamlindent}% \medbreak \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\begin{ocamlindent}This is module X.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module X.\end{ocamlindent}% \medbreak \subsection{Module type\label{module-type}}% -\label{package-test+u+package+++ml-module-Nested-module-type-Y}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-module-type-Y]{\inlinecode{Y}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Type\label{type}}% -\label{package-test+u+package+++ml-module-Nested-module-type-Y-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\begin{ocamlindent}Some type.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-type-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Nested-module-type-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Type\label{type}}% +\label{package-test+u+package+++ml-module-Nested-module-type-Y-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\begin{ocamlindent}Some type.\end{ocamlindent}% \medbreak \subsubsection{Values\label{values}}% -\label{package-test+u+package+++ml-module-Nested-module-type-Y-val-y}\codefragment{\begin{keyword}val\end{keyword} - y : \hyperref[package-test+u+package+++ml-module-Nested-module-type-Y-type-t]{\inlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-type-Y-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : \hyperref[package-test+u+package+++ml-module-Nested-module-type-Y-type-t]{\ocamlinlinecode{t}}}\begin{ocamlindent}The value of y.\end{ocamlindent}% \medbreak \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\begin{ocamlindent}This is module type Y.\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}This is module type Y.\end{ocamlindent}% \medbreak \subsection{Functor\label{functor}}% -\label{package-test+u+package+++ml-module-Nested-module-F}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-module-F]{\inlinecode{F}}}\codefragment{ (\hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1]{\inlinecode{Arg1}} : \hyperref[package-test+u+package+++ml-module-Nested-module-type-Y]{\inlinecode{Y}}) (\hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2]{\inlinecode{Arg2}} : \begin{keyword}sig\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -) : \begin{keyword}sig\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -}\begin{ocamlindent}This is a functor F.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Nested-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ (\hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}} : \hyperref[package-test+u+package+++ml-module-Nested-module-type-Y]{\ocamlinlinecode{Y}}) (\hyperref[package-test+u+package+++ml-module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is a functor F.\end{ocamlindent}% \medbreak \subsection{Class\label{class}}% -\label{package-test+u+package+++ml-module-Nested-class-z}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}virtual\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-class-z]{\inlinecode{z}}}\codefragment{ : \begin{keyword}object\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -}\begin{ocamlindent}This is class z.\end{ocamlindent}% -\medbreak -\label{package-test+u+package+++ml-module-Nested-class-inherits}\codefragment{\begin{keyword}class\end{keyword} - \begin{keyword}virtual\end{keyword} - \hyperref[package-test+u+package+++ml-module-Nested-class-inherits]{\inlinecode{inherits}}}\codefragment{ : \begin{keyword}object\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -}\\ +\label{package-test+u+package+++ml-module-Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[package-test+u+package+++ml-module-Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}% +\medbreak +\label{package-test+u+package+++ml-module-Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[package-test+u+package+++ml-module-Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{test_package+ml/Nested.F.tex} \input{test_package+ml/Nested.z.tex} diff --git a/test/latex/expect/test_package+ml/Nested.z.tex b/test/latex/expect/test_package+ml/Nested.z.tex index 137bc290b8..ca25ac2223 100644 --- a/test/latex/expect/test_package+ml/Nested.z.tex +++ b/test/latex/expect/test_package+ml/Nested.z.tex @@ -1,22 +1,14 @@ -\section{Class \inlinecode{Nested.\allowbreak{}z}}\label{package-test+u+package+++ml-module-Nested-class-z}% +\section{Class \ocamlinlinecode{Nested.\allowbreak{}z}}\label{package-test+u+package+++ml-module-Nested-class-z}% This is class z. Some additional comments. -\label{package-test+u+package+++ml-module-Nested-class-z-val-y}\codefragment{\begin{keyword}val\end{keyword} - y : int}\begin{ocamlindent}Some value.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-class-z-val-y}\ocamlcodefragment{\ocamltag{keyword}{val} y : int}\begin{ocamlindent}Some value.\end{ocamlindent}% \medbreak -\label{package-test+u+package+++ml-module-Nested-class-z-val-y'}\codefragment{\begin{keyword}val\end{keyword} - \begin{keyword}mutable\end{keyword} - \begin{keyword}virtual\end{keyword} - y' : int}\\ +\label{package-test+u+package+++ml-module-Nested-class-z-val-y'}\ocamlcodefragment{\ocamltag{keyword}{val} \ocamltag{keyword}{mutable} \ocamltag{keyword}{virtual} y' : int}\\ \subsection{Methods\label{methods}}% -\label{package-test+u+package+++ml-module-Nested-class-z-method-z}\codefragment{\begin{keyword}method\end{keyword} - z : int}\begin{ocamlindent}Some method.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Nested-class-z-method-z}\ocamlcodefragment{\ocamltag{keyword}{method} z : int}\begin{ocamlindent}Some method.\end{ocamlindent}% \medbreak -\label{package-test+u+package+++ml-module-Nested-class-z-method-z'}\codefragment{\begin{keyword}method\end{keyword} - \begin{keyword}private\end{keyword} - \begin{keyword}virtual\end{keyword} - z' : int}\\ +\label{package-test+u+package+++ml-module-Nested-class-z-method-z'}\ocamlcodefragment{\ocamltag{keyword}{method} \ocamltag{keyword}{private} \ocamltag{keyword}{virtual} z' : int}\\ diff --git a/test/latex/expect/test_package+ml/Recent.tex b/test/latex/expect/test_package+ml/Recent.tex index a87746338a..dc6c4dc994 100644 --- a/test/latex/expect/test_package+ml/Recent.tex +++ b/test/latex/expect/test_package+ml/Recent.tex @@ -1,124 +1,66 @@ -\section{Module \inlinecode{Recent}}\label{package-test+u+package+++ml-module-Recent}% -\label{package-test+u+package+++ml-module-Recent-module-type-S}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-type-S]{\inlinecode{S}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent-module-type-S1}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-type-S1]{\inlinecode{S1}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Recent-module-type-S1-argument-1-+u+}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-type-S1-argument-1-+u+]{\inlinecode{\_\allowbreak{}}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\section{Module \ocamlinlinecode{Recent}}\label{package-test+u+package+++ml-module-Recent}% +\label{package-test+u+package+++ml-module-Recent-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Recent-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent-module-type-S1}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Recent-module-type-S1]{\ocamlinlinecode{S1}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{package-test+u+package+++ml-module-Recent-module-type-S1-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent-module-type-S1-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent-type-variant}\codefragment{\begin{keyword}type\end{keyword} - variant = }\\ -\codefragment{| \begin{constructor}A\end{constructor} -}\label{package-test+u+package+++ml-module-Recent-type-variant.A}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }\\ +\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{package-test+u+package+++ml-module-Recent-type-variant.A}% \begin{ocamlindent}\end{ocamlindent}% -\codefragment{| \begin{constructor}B\end{constructor} - \begin{keyword}of\end{keyword} - int}\label{package-test+u+package+++ml-module-Recent-type-variant.B}% +\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{package-test+u+package+++ml-module-Recent-type-variant.B}% \begin{ocamlindent}\end{ocamlindent}% -\codefragment{| \begin{constructor}C\end{constructor} -}\label{package-test+u+package+++ml-module-Recent-type-variant.C}% +\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{package-test+u+package+++ml-module-Recent-type-variant.C}% \begin{ocamlindent}foo\end{ocamlindent}% -\codefragment{| \begin{constructor}D\end{constructor} -}\label{package-test+u+package+++ml-module-Recent-type-variant.D}% +\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{package-test+u+package+++ml-module-Recent-type-variant.D}% \begin{ocamlindent}\emph{bar}\end{ocamlindent}% -\codefragment{| \begin{constructor}E\end{constructor} - \begin{keyword}of\end{keyword} - \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Recent-type-variant.a}\\ -\end{longtable}% -}\codefragment{\}}\label{package-test+u+package+++ml-module-Recent-type-variant.E}% +\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Recent-type-variant.a}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{\}}\label{package-test+u+package+++ml-module-Recent-type-variant.E}% \begin{ocamlindent}\end{ocamlindent}% -\label{package-test+u+package+++ml-module-Recent-type-gadt}\codefragment{\begin{keyword}type\end{keyword} - \_\allowbreak{} gadt = }\\ -\codefragment{| \begin{constructor}A\end{constructor} - : int \hyperref[package-test+u+package+++ml-module-Recent-type-gadt]{\inlinecode{gadt}}}\label{package-test+u+package+++ml-module-Recent-type-gadt.A}% +\label{package-test+u+package+++ml-module-Recent-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }\\ +\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[package-test+u+package+++ml-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{package-test+u+package+++ml-module-Recent-type-gadt.A}% \begin{ocamlindent}\end{ocamlindent}% -\codefragment{| \begin{constructor}B\end{constructor} - : int $\rightarrow$ string \hyperref[package-test+u+package+++ml-module-Recent-type-gadt]{\inlinecode{gadt}}}\label{package-test+u+package+++ml-module-Recent-type-gadt.B}% +\ocamlcodefragment{| \ocamltag{constructor}{B} : int $\rightarrow$ string \hyperref[package-test+u+package+++ml-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{package-test+u+package+++ml-module-Recent-type-gadt.B}% \begin{ocamlindent}foo\end{ocamlindent}% -\codefragment{| \begin{constructor}C\end{constructor} - : \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Recent-type-gadt.a}\\ -\end{longtable}% -}\codefragment{\} $\rightarrow$ unit \hyperref[package-test+u+package+++ml-module-Recent-type-gadt]{\inlinecode{gadt}}}\label{package-test+u+package+++ml-module-Recent-type-gadt.C}% +\ocamlcodefragment{| \ocamltag{constructor}{C} : \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Recent-type-gadt.a}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{\} $\rightarrow$ unit \hyperref[package-test+u+package+++ml-module-Recent-type-gadt]{\ocamlinlinecode{gadt}}}\label{package-test+u+package+++ml-module-Recent-type-gadt.C}% \begin{ocamlindent}\end{ocamlindent}% -\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant}\codefragment{\begin{keyword}type\end{keyword} - polymorphic\_\allowbreak{}variant = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\inlinecode{| }\inlinecode{`A}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.A}& \\ -\inlinecode{| }\inlinecode{`B \begin{keyword}of\end{keyword} - int}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.B}& \\ -\inlinecode{| }\inlinecode{`C}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.C}& foo\\ -\inlinecode{| }\inlinecode{`D}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.D}& bar\\ -\end{longtable}% -}\codefragment{ ]}\\ -\label{package-test+u+package+++ml-module-Recent-type-empty+u+variant}\codefragment{\begin{keyword}type\end{keyword} - empty\_\allowbreak{}variant = |}\\ -\label{package-test+u+package+++ml-module-Recent-type-nonrec+u+}\codefragment{\begin{keyword}type\end{keyword} - \begin{keyword}nonrec\end{keyword} - nonrec\_\allowbreak{} = int}\\ -\label{package-test+u+package+++ml-module-Recent-type-empty+u+conj}\codefragment{\begin{keyword}type\end{keyword} - empty\_\allowbreak{}conj = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}X\end{constructor} - : [< `X of \& \begin{type-var}'a\end{type-var} - \& int * float ] $\rightarrow$ \hyperref[package-test+u+package+++ml-module-Recent-type-empty+u+conj]{\inlinecode{empty\_\allowbreak{}conj}}}\label{package-test+u+package+++ml-module-Recent-type-empty+u+conj.X}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Recent-type-conj}\codefragment{\begin{keyword}type\end{keyword} - conj = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}X\end{constructor} - : [< `X of int \& [< `B of int \& float ] ] $\rightarrow$ \hyperref[package-test+u+package+++ml-module-Recent-type-conj]{\inlinecode{conj}}}\label{package-test+u+package+++ml-module-Recent-type-conj.X}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Recent-val-empty+u+conj}\codefragment{\begin{keyword}val\end{keyword} - empty\_\allowbreak{}conj : [< `X of \& \begin{type-var}'a\end{type-var} - \& int * float ]}\\ -\label{package-test+u+package+++ml-module-Recent-val-conj}\codefragment{\begin{keyword}val\end{keyword} - conj : [< `X of int \& [< `B of int \& float ] ]}\\ -\label{package-test+u+package+++ml-module-Recent-module-Z}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-Z]{\inlinecode{Z}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-Z-module-Y}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y]{\inlinecode{Y}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X]{\inlinecode{X}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t}\codefragment{\begin{keyword}type\end{keyword} - 'a t}\\ +\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.A}& \\ +\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} int}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.B}& \\ +\ocamlinlinecode{| }\ocamlinlinecode{`C}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.C}& foo\\ +\ocamlinlinecode{| }\ocamlinlinecode{`D}\label{package-test+u+package+++ml-module-Recent-type-polymorphic+u+variant.D}& bar\\ +\end{ocamllongtable}% +}\ocamlcodefragment{ ]}\\ +\label{package-test+u+package+++ml-module-Recent-type-empty+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}variant = |}\\ +\label{package-test+u+package+++ml-module-Recent-type-nonrec+u+}\ocamlcodefragment{\ocamltag{keyword}{type} \ocamltag{keyword}{nonrec} nonrec\_\allowbreak{} = int}\\ +\label{package-test+u+package+++ml-module-Recent-type-empty+u+conj}\ocamlcodefragment{\ocamltag{keyword}{type} empty\_\allowbreak{}conj = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of \& \ocamltag{type-var}{'a} \& int * float ] $\rightarrow$ \hyperref[package-test+u+package+++ml-module-Recent-type-empty+u+conj]{\ocamlinlinecode{empty\_\allowbreak{}conj}}}\label{package-test+u+package+++ml-module-Recent-type-empty+u+conj.X}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Recent-type-conj}\ocamlcodefragment{\ocamltag{keyword}{type} conj = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{X} : [< `X of int \& [< `B of int \& float ] ] $\rightarrow$ \hyperref[package-test+u+package+++ml-module-Recent-type-conj]{\ocamlinlinecode{conj}}}\label{package-test+u+package+++ml-module-Recent-type-conj.X}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Recent-val-empty+u+conj}\ocamlcodefragment{\ocamltag{keyword}{val} empty\_\allowbreak{}conj : [< `X of \& \ocamltag{type-var}{'a} \& int * float ]}\\ +\label{package-test+u+package+++ml-module-Recent-val-conj}\ocamlcodefragment{\ocamltag{keyword}{val} conj : [< `X of int \& [< `B of int \& float ] ]}\\ +\label{package-test+u+package+++ml-module-Recent-module-Z}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent-module-Z]{\ocamlinlinecode{Z}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-Z-module-Y}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y]{\ocamlinlinecode{Y}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} 'a t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent-module-X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-X]{\inlinecode{X}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-X-module-L}\codefragment{\begin{keyword}module\end{keyword} - L := \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y]{\inlinecode{Z.\allowbreak{}Y}}}\\ -\label{package-test+u+package+++ml-module-Recent-module-X-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = int \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t]{\inlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\ -\label{package-test+u+package+++ml-module-Recent-module-X-type-u}\codefragment{\begin{keyword}type\end{keyword} - u := int}\\ -\label{package-test+u+package+++ml-module-Recent-module-X-type-v}\codefragment{\begin{keyword}type\end{keyword} - v = \hyperref[package-test+u+package+++ml-module-Recent-module-X-type-u]{\inlinecode{u}} \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t]{\inlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-X-module-L}\ocamlcodefragment{\ocamltag{keyword}{module} L := \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y]{\ocamlinlinecode{Z.\allowbreak{}Y}}}\\ +\label{package-test+u+package+++ml-module-Recent-module-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\ +\label{package-test+u+package+++ml-module-Recent-module-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u := int}\\ +\label{package-test+u+package+++ml-module-Recent-module-X-type-v}\ocamlcodefragment{\ocamltag{keyword}{type} v = \hyperref[package-test+u+package+++ml-module-Recent-module-X-type-u]{\ocamlinlinecode{u}} \hyperref[package-test+u+package+++ml-module-Recent-module-Z-module-Y-module-X-type-t]{\ocamlinlinecode{Z.\allowbreak{}Y.\allowbreak{}X.\allowbreak{}t}}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent-module-type-PolyS}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent-module-type-PolyS]{\inlinecode{PolyS}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-type-PolyS-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{| }\inlinecode{`A}\label{package-test+u+package+++ml-module-Recent-module-type-PolyS-type-t.A}\\ -\inlinecode{| }\inlinecode{`B}\label{package-test+u+package+++ml-module-Recent-module-type-PolyS-type-t.B}\\ -\end{longtable}% -}\codefragment{ ]}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent-module-type-PolyS}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Recent-module-type-PolyS]{\ocamlinlinecode{PolyS}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent-module-type-PolyS-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{package-test+u+package+++ml-module-Recent-module-type-PolyS-type-t.A}\\ +\ocamlinlinecode{| }\ocamlinlinecode{`B}\label{package-test+u+package+++ml-module-Recent-module-type-PolyS-type-t.B}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{ ]}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ diff --git a/test/latex/expect/test_package+ml/Recent_impl.B.tex b/test/latex/expect/test_package+ml/Recent_impl.B.tex index 63ab84c297..1b9d8233c6 100644 --- a/test/latex/expect/test_package+ml/Recent_impl.B.tex +++ b/test/latex/expect/test_package+ml/Recent_impl.B.tex @@ -1,7 +1,5 @@ -\section{Module \inlinecode{Recent\_\allowbreak{}impl.\allowbreak{}B}}\label{package-test+u+package+++ml-module-Recent+u+impl-module-B}% -\label{package-test+u+package+++ml-module-Recent+u+impl-module-B-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}B\end{constructor} -}\label{package-test+u+package+++ml-module-Recent+u+impl-module-B-type-t.B}\\ -\end{longtable}% +\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl.\allowbreak{}B}}\label{package-test+u+package+++ml-module-Recent+u+impl-module-B}% +\label{package-test+u+package+++ml-module-Recent+u+impl-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{package-test+u+package+++ml-module-Recent+u+impl-module-B-type-t.B}\\ +\end{ocamllongtable}% } diff --git a/test/latex/expect/test_package+ml/Recent_impl.tex b/test/latex/expect/test_package+ml/Recent_impl.tex index 6246f457eb..d5b42d7d50 100644 --- a/test/latex/expect/test_package+ml/Recent_impl.tex +++ b/test/latex/expect/test_package+ml/Recent_impl.tex @@ -1,61 +1,28 @@ -\section{Module \inlinecode{Recent\_\allowbreak{}impl}}\label{package-test+u+package+++ml-module-Recent+u+impl}% -\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo]{\inlinecode{Foo}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A]{\inlinecode{A}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}A\end{constructor} -}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A-type-t.A}\\ -\end{longtable}% +\section{Module \ocamlinlinecode{Recent\_\allowbreak{}impl}}\label{package-test+u+package+++ml-module-Recent+u+impl}% +\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo]{\ocamlinlinecode{Foo}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A]{\ocamlinlinecode{A}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-A-type-t.A}\\ +\end{ocamllongtable}% }\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B]{\inlinecode{B}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B-type-t}\codefragment{\begin{keyword}type\end{keyword} - t = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}B\end{constructor} -}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B-type-t.B}\\ -\end{longtable}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B}}\label{package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B-type-t.B}\\ +\end{ocamllongtable}% }\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-module-B}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-B]{\inlinecode{B}}}\codefragment{ : \begin{keyword}sig\end{keyword} - .\allowbreak{}.\allowbreak{}.\allowbreak{} \begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S]{\inlinecode{S}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F]{\inlinecode{F}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% -\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+]{\inlinecode{\_\allowbreak{}}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-B}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-B]{\ocamlinlinecode{B}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Parameters\label{parameters}}% +\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-argument-1-+u+]{\ocamlinlinecode{\_\allowbreak{}}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ \subsubsection{Signature\label{signature}}% -\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-X}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-X]{\inlinecode{X}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-val-f}\codefragment{\begin{keyword}val\end{keyword} - f : \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-type-t]{\inlinecode{F(X).\allowbreak{}t}}}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-X}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\end{ocamlindent}% +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-type-S-val-f}\ocamlcodefragment{\ocamltag{keyword}{val} f : \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-type-S-module-F-type-t]{\ocamlinlinecode{F(X).\allowbreak{}t}}}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Recent+u+impl-module-B'}\codefragment{\begin{keyword}module\end{keyword} - B' = \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B]{\inlinecode{Foo.\allowbreak{}B}}}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Recent+u+impl-module-B'}\ocamlcodefragment{\ocamltag{keyword}{module} B' = \hyperref[package-test+u+package+++ml-module-Recent+u+impl-module-Foo-module-B]{\ocamlinlinecode{Foo.\allowbreak{}B}}}\\ \input{test_package+ml/Recent_impl.B.tex} diff --git a/test/latex/expect/test_package+ml/Section.tex b/test/latex/expect/test_package+ml/Section.tex index ac0323f20a..e390b32bc3 100644 --- a/test/latex/expect/test_package+ml/Section.tex +++ b/test/latex/expect/test_package+ml/Section.tex @@ -1,4 +1,4 @@ -\section{Module \inlinecode{Section}}\label{package-test+u+package+++ml-module-Section}% +\section{Module \ocamlinlinecode{Section}}\label{package-test+u+package+++ml-module-Section}% This is the module comment. Eventually, sections won't be allowed in it. \subsection{Empty section\label{empty-section}}% @@ -9,12 +9,11 @@ \subsection{Aside only\label{aside-only}}% Foo bar. \subsection{Value only\label{value-only}}% -\label{package-test+u+package+++ml-module-Section-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : unit}\\ +\label{package-test+u+package+++ml-module-Section-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : unit}\\ \subsection{Empty section\label{empty-section}}% \subsection{within a comment\label{within-a-comment}}% \subsubsection{and one with a nested section\label{and-one-with-a-nested-section}}% -\subsection{\emph{This} \inlinecode{section} \textbf{title} \textsubscript{has} \textsuperscript{markup}\label{this-section-title-has-markup}}% +\subsection{\emph{This} \ocamlinlinecode{section} \bold{title} \textsubscript{has} \textsuperscript{markup}\label{this-section-title-has-markup}}% But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. diff --git a/test/latex/expect/test_package+ml/Stop.tex b/test/latex/expect/test_package+ml/Stop.tex index 73bba279f3..81872b59cf 100644 --- a/test/latex/expect/test_package+ml/Stop.tex +++ b/test/latex/expect/test_package+ml/Stop.tex @@ -1,23 +1,17 @@ -\section{Module \inlinecode{Stop}}\label{package-test+u+package+++ml-module-Stop}% +\section{Module \ocamlinlinecode{Stop}}\label{package-test+u+package+++ml-module-Stop}% This test cases exercises stop comments. -\label{package-test+u+package+++ml-module-Stop-val-foo}\codefragment{\begin{keyword}val\end{keyword} - foo : int}\begin{ocamlindent}This is normal commented text.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Stop-val-foo}\ocamlcodefragment{\ocamltag{keyword}{val} foo : int}\begin{ocamlindent}This is normal commented text.\end{ocamlindent}% \medbreak -The next value is \inlinecode{bar}, and it should be missing from the documentation. There is also an entire module, \inlinecode{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. +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. Documentation is on again. Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module. -\label{package-test+u+package+++ml-module-Stop-module-N}\codefragment{\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Stop-module-N]{\inlinecode{N}}}\codefragment{ : \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Stop-module-N-val-quux}\codefragment{\begin{keyword}val\end{keyword} - quux : int}\\ +\label{package-test+u+package+++ml-module-Stop-module-N}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Stop-module-N]{\ocamlinlinecode{N}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Stop-module-N-val-quux}\ocamlcodefragment{\ocamltag{keyword}{val} quux : int}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Stop-val-lol}\codefragment{\begin{keyword}val\end{keyword} - lol : int}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Stop-val-lol}\ocamlcodefragment{\ocamltag{keyword}{val} lol : int}\\ diff --git a/test/latex/expect/test_package+ml/Type.tex b/test/latex/expect/test_package+ml/Type.tex index 9c636abd9d..cb31b47ab7 100644 --- a/test/latex/expect/test_package+ml/Type.tex +++ b/test/latex/expect/test_package+ml/Type.tex @@ -1,223 +1,95 @@ -\section{Module \inlinecode{Type}}\label{package-test+u+package+++ml-module-Type}% -\label{package-test+u+package+++ml-module-Type-type-abstract}\codefragment{\begin{keyword}type\end{keyword} - abstract}\begin{ocamlindent}Some \emph{documentation}.\end{ocamlindent}% +\section{Module \ocamlinlinecode{Type}}\label{package-test+u+package+++ml-module-Type}% +\label{package-test+u+package+++ml-module-Type-type-abstract}\ocamlcodefragment{\ocamltag{keyword}{type} abstract}\begin{ocamlindent}Some \emph{documentation}.\end{ocamlindent}% \medbreak -\label{package-test+u+package+++ml-module-Type-type-alias}\codefragment{\begin{keyword}type\end{keyword} - alias = int}\\ -\label{package-test+u+package+++ml-module-Type-type-private+u+}\codefragment{\begin{keyword}type\end{keyword} - private\_\allowbreak{} = \begin{keyword}private\end{keyword} - int}\\ -\label{package-test+u+package+++ml-module-Type-type-constructor}\codefragment{\begin{keyword}type\end{keyword} - 'a constructor = \begin{type-var}'a\end{type-var} -}\\ -\label{package-test+u+package+++ml-module-Type-type-arrow}\codefragment{\begin{keyword}type\end{keyword} - arrow = int $\rightarrow$ int}\\ -\label{package-test+u+package+++ml-module-Type-type-higher+u+order}\codefragment{\begin{keyword}type\end{keyword} - higher\_\allowbreak{}order = (int $\rightarrow$ int) $\rightarrow$ int}\\ -\label{package-test+u+package+++ml-module-Type-type-labeled}\codefragment{\begin{keyword}type\end{keyword} - labeled = l:int $\rightarrow$ int}\\ -\label{package-test+u+package+++ml-module-Type-type-optional}\codefragment{\begin{keyword}type\end{keyword} - optional = ?l:int $\rightarrow$ int}\\ -\label{package-test+u+package+++ml-module-Type-type-labeled+u+higher+u+order}\codefragment{\begin{keyword}type\end{keyword} - labeled\_\allowbreak{}higher\_\allowbreak{}order = (l:int $\rightarrow$ int) $\rightarrow$ (?l:int $\rightarrow$ int) $\rightarrow$ int}\\ -\label{package-test+u+package+++ml-module-Type-type-pair}\codefragment{\begin{keyword}type\end{keyword} - pair = int * int}\\ -\label{package-test+u+package+++ml-module-Type-type-parens+u+dropped}\codefragment{\begin{keyword}type\end{keyword} - parens\_\allowbreak{}dropped = int * int}\\ -\label{package-test+u+package+++ml-module-Type-type-triple}\codefragment{\begin{keyword}type\end{keyword} - triple = int * int * int}\\ -\label{package-test+u+package+++ml-module-Type-type-nested+u+pair}\codefragment{\begin{keyword}type\end{keyword} - nested\_\allowbreak{}pair = (int * int) * int}\\ -\label{package-test+u+package+++ml-module-Type-type-instance}\codefragment{\begin{keyword}type\end{keyword} - instance = int \hyperref[package-test+u+package+++ml-module-Type-type-constructor]{\inlinecode{constructor}}}\\ -\label{package-test+u+package+++ml-module-Type-type-variant+u+e}\codefragment{\begin{keyword}type\end{keyword} - variant\_\allowbreak{}e = \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-variant+u+e.a}\\ -\end{longtable}% -}\codefragment{\}}\\ -\label{package-test+u+package+++ml-module-Type-type-variant}\codefragment{\begin{keyword}type\end{keyword} - variant = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\codefragment{| \begin{constructor}A\end{constructor} -}\label{package-test+u+package+++ml-module-Type-type-variant.A}& \\ -\codefragment{| \begin{constructor}B\end{constructor} - \begin{keyword}of\end{keyword} - int}\label{package-test+u+package+++ml-module-Type-type-variant.B}& \\ -\codefragment{| \begin{constructor}C\end{constructor} -}\label{package-test+u+package+++ml-module-Type-type-variant.C}& foo\\ -\codefragment{| \begin{constructor}D\end{constructor} -}\label{package-test+u+package+++ml-module-Type-type-variant.D}& \emph{bar}\\ -\codefragment{| \begin{constructor}E\end{constructor} - \begin{keyword}of\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-type-variant+u+e]{\inlinecode{variant\_\allowbreak{}e}}}\label{package-test+u+package+++ml-module-Type-type-variant.E}& \\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-type-variant+u+c}\codefragment{\begin{keyword}type\end{keyword} - variant\_\allowbreak{}c = \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-variant+u+c.a}\\ -\end{longtable}% -}\codefragment{\}}\\ -\label{package-test+u+package+++ml-module-Type-type-gadt}\codefragment{\begin{keyword}type\end{keyword} - \_\allowbreak{} gadt = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}A\end{constructor} - : int \hyperref[package-test+u+package+++ml-module-Type-type-gadt]{\inlinecode{gadt}}}\label{package-test+u+package+++ml-module-Type-type-gadt.A}\\ -\codefragment{| \begin{constructor}B\end{constructor} - : int $\rightarrow$ string \hyperref[package-test+u+package+++ml-module-Type-type-gadt]{\inlinecode{gadt}}}\label{package-test+u+package+++ml-module-Type-type-gadt.B}\\ -\codefragment{| \begin{constructor}C\end{constructor} - : \hyperref[package-test+u+package+++ml-module-Type-type-variant+u+c]{\inlinecode{variant\_\allowbreak{}c}} $\rightarrow$ unit \hyperref[package-test+u+package+++ml-module-Type-type-gadt]{\inlinecode{gadt}}}\label{package-test+u+package+++ml-module-Type-type-gadt.C}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-type-degenerate+u+gadt}\codefragment{\begin{keyword}type\end{keyword} - degenerate\_\allowbreak{}gadt = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}A\end{constructor} - : \hyperref[package-test+u+package+++ml-module-Type-type-degenerate+u+gadt]{\inlinecode{degenerate\_\allowbreak{}gadt}}}\label{package-test+u+package+++ml-module-Type-type-degenerate+u+gadt.A}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-type-private+u+variant}\codefragment{\begin{keyword}type\end{keyword} - private\_\allowbreak{}variant = \begin{keyword}private\end{keyword} - }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}A\end{constructor} -}\label{package-test+u+package+++ml-module-Type-type-private+u+variant.A}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-type-record}\codefragment{\begin{keyword}type\end{keyword} - record = \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\inlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.a}& \\ -\inlinecode{\begin{keyword}mutable\end{keyword} - b : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.b}& \\ -\inlinecode{c : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.c}& foo\\ -\inlinecode{d : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.d}& \emph{bar}\\ -\inlinecode{e : a.\allowbreak{} \begin{type-var}'a\end{type-var} -;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.e}& \\ -\end{longtable}% -}\codefragment{\}}\\ -\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant}\codefragment{\begin{keyword}type\end{keyword} - polymorphic\_\allowbreak{}variant = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{| }\inlinecode{`A}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.A}\\ -\inlinecode{| }\inlinecode{`B \begin{keyword}of\end{keyword} - int}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.B}\\ -\inlinecode{| }\inlinecode{`C \begin{keyword}of\end{keyword} - int * unit}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.C}\\ -\inlinecode{| }\inlinecode{`D}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.D}\\ -\end{longtable}% -}\codefragment{ ]}\\ -\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension}\codefragment{\begin{keyword}type\end{keyword} - polymorphic\_\allowbreak{}variant\_\allowbreak{}extension = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{| }\inlinecode{\hyperref[package-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\inlinecode{polymorphic\_\allowbreak{}variant}}}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension.polymorphic+u+variant}\\ -\inlinecode{| }\inlinecode{`E}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension.E}\\ -\end{longtable}% -}\codefragment{ ]}\\ -\label{package-test+u+package+++ml-module-Type-type-nested+u+polymorphic+u+variant}\codefragment{\begin{keyword}type\end{keyword} - nested\_\allowbreak{}polymorphic\_\allowbreak{}variant = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{| }\inlinecode{`A \begin{keyword}of\end{keyword} - [ `B | `C ]}\label{package-test+u+package+++ml-module-Type-type-nested+u+polymorphic+u+variant.A}\\ -\end{longtable}% -}\codefragment{ ]}\\ -\label{package-test+u+package+++ml-module-Type-type-private+u+extenion#row}\codefragment{\begin{keyword}type\end{keyword} - private\_\allowbreak{}extenion\#row}\\ -\label{package-test+u+package+++ml-module-Type-type-private+u+extenion}\codefragment{\begin{keyword}and\end{keyword} - private\_\allowbreak{}extenion = \begin{keyword}private\end{keyword} - [> }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\inlinecode{| }\inlinecode{\hyperref[package-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\inlinecode{polymorphic\_\allowbreak{}variant}}}\label{package-test+u+package+++ml-module-Type-type-private+u+extenion.polymorphic+u+variant}\\ -\end{longtable}% -}\codefragment{ ]}\\ -\label{package-test+u+package+++ml-module-Type-type-object+u+}\codefragment{\begin{keyword}type\end{keyword} - object\_\allowbreak{} = < a : int;\allowbreak{} b : int;\allowbreak{} c : int;\allowbreak{} >}\\ -\label{package-test+u+package+++ml-module-Type-module-type-X}\codefragment{\begin{keyword}module\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-module-type-X]{\inlinecode{X}}}\codefragment{ = \begin{keyword}sig\end{keyword} -}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Type-module-type-X-type-t}\codefragment{\begin{keyword}type\end{keyword} - t}\\ -\label{package-test+u+package+++ml-module-Type-module-type-X-type-u}\codefragment{\begin{keyword}type\end{keyword} - u}\\ +\label{package-test+u+package+++ml-module-Type-type-alias}\ocamlcodefragment{\ocamltag{keyword}{type} alias = int}\\ +\label{package-test+u+package+++ml-module-Type-type-private+u+}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{} = \ocamltag{keyword}{private} int}\\ +\label{package-test+u+package+++ml-module-Type-type-constructor}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constructor = \ocamltag{type-var}{'a}}\\ +\label{package-test+u+package+++ml-module-Type-type-arrow}\ocamlcodefragment{\ocamltag{keyword}{type} arrow = int $\rightarrow$ int}\\ +\label{package-test+u+package+++ml-module-Type-type-higher+u+order}\ocamlcodefragment{\ocamltag{keyword}{type} higher\_\allowbreak{}order = (int $\rightarrow$ int) $\rightarrow$ int}\\ +\label{package-test+u+package+++ml-module-Type-type-labeled}\ocamlcodefragment{\ocamltag{keyword}{type} labeled = l:int $\rightarrow$ int}\\ +\label{package-test+u+package+++ml-module-Type-type-optional}\ocamlcodefragment{\ocamltag{keyword}{type} optional = ?l:int $\rightarrow$ int}\\ +\label{package-test+u+package+++ml-module-Type-type-labeled+u+higher+u+order}\ocamlcodefragment{\ocamltag{keyword}{type} labeled\_\allowbreak{}higher\_\allowbreak{}order = (l:int $\rightarrow$ int) $\rightarrow$ (?l:int $\rightarrow$ int) $\rightarrow$ int}\\ +\label{package-test+u+package+++ml-module-Type-type-pair}\ocamlcodefragment{\ocamltag{keyword}{type} pair = int * int}\\ +\label{package-test+u+package+++ml-module-Type-type-parens+u+dropped}\ocamlcodefragment{\ocamltag{keyword}{type} parens\_\allowbreak{}dropped = int * int}\\ +\label{package-test+u+package+++ml-module-Type-type-triple}\ocamlcodefragment{\ocamltag{keyword}{type} triple = int * int * int}\\ +\label{package-test+u+package+++ml-module-Type-type-nested+u+pair}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}pair = (int * int) * int}\\ +\label{package-test+u+package+++ml-module-Type-type-instance}\ocamlcodefragment{\ocamltag{keyword}{type} instance = int \hyperref[package-test+u+package+++ml-module-Type-type-constructor]{\ocamlinlinecode{constructor}}}\\ +\label{package-test+u+package+++ml-module-Type-type-variant+u+e}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}e = \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-variant+u+e.a}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{\}}\\ +\label{package-test+u+package+++ml-module-Type-type-variant}\ocamlcodefragment{\ocamltag{keyword}{type} variant = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{package-test+u+package+++ml-module-Type-type-variant.A}& \\ +\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} int}\label{package-test+u+package+++ml-module-Type-type-variant.B}& \\ +\ocamlcodefragment{| \ocamltag{constructor}{C}}\label{package-test+u+package+++ml-module-Type-type-variant.C}& foo\\ +\ocamlcodefragment{| \ocamltag{constructor}{D}}\label{package-test+u+package+++ml-module-Type-type-variant.D}& \emph{bar}\\ +\ocamlcodefragment{| \ocamltag{constructor}{E} \ocamltag{keyword}{of} \hyperref[package-test+u+package+++ml-module-Type-type-variant+u+e]{\ocamlinlinecode{variant\_\allowbreak{}e}}}\label{package-test+u+package+++ml-module-Type-type-variant.E}& \\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-type-variant+u+c}\ocamlcodefragment{\ocamltag{keyword}{type} variant\_\allowbreak{}c = \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-variant+u+c.a}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{\}}\\ +\label{package-test+u+package+++ml-module-Type-type-gadt}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} gadt = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : int \hyperref[package-test+u+package+++ml-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{package-test+u+package+++ml-module-Type-type-gadt.A}\\ +\ocamlcodefragment{| \ocamltag{constructor}{B} : int $\rightarrow$ string \hyperref[package-test+u+package+++ml-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{package-test+u+package+++ml-module-Type-type-gadt.B}\\ +\ocamlcodefragment{| \ocamltag{constructor}{C} : \hyperref[package-test+u+package+++ml-module-Type-type-variant+u+c]{\ocamlinlinecode{variant\_\allowbreak{}c}} $\rightarrow$ unit \hyperref[package-test+u+package+++ml-module-Type-type-gadt]{\ocamlinlinecode{gadt}}}\label{package-test+u+package+++ml-module-Type-type-gadt.C}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-type-degenerate+u+gadt}\ocamlcodefragment{\ocamltag{keyword}{type} degenerate\_\allowbreak{}gadt = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} : \hyperref[package-test+u+package+++ml-module-Type-type-degenerate+u+gadt]{\ocamlinlinecode{degenerate\_\allowbreak{}gadt}}}\label{package-test+u+package+++ml-module-Type-type-degenerate+u+gadt.A}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-type-private+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}variant = \ocamltag{keyword}{private} }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A}}\label{package-test+u+package+++ml-module-Type-type-private+u+variant.A}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-type-record}\ocamlcodefragment{\ocamltag{keyword}{type} record = \{}{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\ocamlinlinecode{a : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.a}& \\ +\ocamlinlinecode{\ocamltag{keyword}{mutable} b : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.b}& \\ +\ocamlinlinecode{c : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.c}& foo\\ +\ocamlinlinecode{d : int;\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.d}& \emph{bar}\\ +\ocamlinlinecode{e : a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{}}\label{package-test+u+package+++ml-module-Type-type-record.e}& \\ +\end{ocamllongtable}% +}\ocamlcodefragment{\}}\\ +\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.A}\\ +\ocamlinlinecode{| }\ocamlinlinecode{`B \ocamltag{keyword}{of} int}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.B}\\ +\ocamlinlinecode{| }\ocamlinlinecode{`C \ocamltag{keyword}{of} int * unit}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.C}\\ +\ocamlinlinecode{| }\ocamlinlinecode{`D}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant.D}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{ ]}\\ +\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension}\ocamlcodefragment{\ocamltag{keyword}{type} polymorphic\_\allowbreak{}variant\_\allowbreak{}extension = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[package-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension.polymorphic+u+variant}\\ +\ocamlinlinecode{| }\ocamlinlinecode{`E}\label{package-test+u+package+++ml-module-Type-type-polymorphic+u+variant+u+extension.E}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{ ]}\\ +\label{package-test+u+package+++ml-module-Type-type-nested+u+polymorphic+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} nested\_\allowbreak{}polymorphic\_\allowbreak{}variant = [ }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{`A \ocamltag{keyword}{of} [ `B | `C ]}\label{package-test+u+package+++ml-module-Type-type-nested+u+polymorphic+u+variant.A}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{ ]}\\ +\label{package-test+u+package+++ml-module-Type-type-private+u+extenion#row}\ocamlcodefragment{\ocamltag{keyword}{type} private\_\allowbreak{}extenion\#row}\\ +\label{package-test+u+package+++ml-module-Type-type-private+u+extenion}\ocamlcodefragment{\ocamltag{keyword}{and} private\_\allowbreak{}extenion = \ocamltag{keyword}{private} [> }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlinlinecode{| }\ocamlinlinecode{\hyperref[package-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}}}\label{package-test+u+package+++ml-module-Type-type-private+u+extenion.polymorphic+u+variant}\\ +\end{ocamllongtable}% +}\ocamlcodefragment{ ]}\\ +\label{package-test+u+package+++ml-module-Type-type-object+u+}\ocamlcodefragment{\ocamltag{keyword}{type} object\_\allowbreak{} = < a : int;\allowbreak{} b : int;\allowbreak{} c : int;\allowbreak{} >}\\ +\label{package-test+u+package+++ml-module-Type-module-type-X}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Type-module-type-X]{\ocamlinlinecode{X}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{package-test+u+package+++ml-module-Type-module-type-X-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ +\label{package-test+u+package+++ml-module-Type-module-type-X-type-u}\ocamlcodefragment{\ocamltag{keyword}{type} u}\\ \end{ocamlindent}% -\codefragment{\begin{keyword}end\end{keyword} -}\\ -\label{package-test+u+package+++ml-module-Type-type-module+u+}\codefragment{\begin{keyword}type\end{keyword} - module\_\allowbreak{} = (\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-module-type-X]{\inlinecode{X}})}\\ -\label{package-test+u+package+++ml-module-Type-type-module+u+substitution}\codefragment{\begin{keyword}type\end{keyword} - module\_\allowbreak{}substitution = (\begin{keyword}module\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-module-type-X]{\inlinecode{X}} \begin{keyword}with\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-module-type-X-type-t]{\inlinecode{t}} = int \begin{keyword}and\end{keyword} - \begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-module-type-X-type-u]{\inlinecode{u}} = unit)}\\ -\label{package-test+u+package+++ml-module-Type-type-covariant}\codefragment{\begin{keyword}type\end{keyword} - +'a covariant}\\ -\label{package-test+u+package+++ml-module-Type-type-contravariant}\codefragment{\begin{keyword}type\end{keyword} - -'a contravariant}\\ -\label{package-test+u+package+++ml-module-Type-type-bivariant}\codefragment{\begin{keyword}type\end{keyword} - \_\allowbreak{} bivariant = int}\\ -\label{package-test+u+package+++ml-module-Type-type-binary}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) binary}\\ -\label{package-test+u+package+++ml-module-Type-type-using+u+binary}\codefragment{\begin{keyword}type\end{keyword} - using\_\allowbreak{}binary = (int,\allowbreak{} int) \hyperref[package-test+u+package+++ml-module-Type-type-binary]{\inlinecode{binary}}}\\ -\label{package-test+u+package+++ml-module-Type-type-name}\codefragment{\begin{keyword}type\end{keyword} - 'custom name}\\ -\label{package-test+u+package+++ml-module-Type-type-constrained}\codefragment{\begin{keyword}type\end{keyword} - 'a constrained = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = int}\\ -\label{package-test+u+package+++ml-module-Type-type-exact+u+variant}\codefragment{\begin{keyword}type\end{keyword} - 'a exact\_\allowbreak{}variant = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = [ `A | `B of int ]}\\ -\label{package-test+u+package+++ml-module-Type-type-lower+u+variant}\codefragment{\begin{keyword}type\end{keyword} - 'a lower\_\allowbreak{}variant = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = [> `A | `B of int ]}\\ -\label{package-test+u+package+++ml-module-Type-type-any+u+variant}\codefragment{\begin{keyword}type\end{keyword} - 'a any\_\allowbreak{}variant = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = [> ]}\\ -\label{package-test+u+package+++ml-module-Type-type-upper+u+variant}\codefragment{\begin{keyword}type\end{keyword} - 'a upper\_\allowbreak{}variant = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = [< `A | `B of int ]}\\ -\label{package-test+u+package+++ml-module-Type-type-named+u+variant}\codefragment{\begin{keyword}type\end{keyword} - 'a named\_\allowbreak{}variant = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = [< \hyperref[package-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\inlinecode{polymorphic\_\allowbreak{}variant}} ]}\\ -\label{package-test+u+package+++ml-module-Type-type-exact+u+object}\codefragment{\begin{keyword}type\end{keyword} - 'a exact\_\allowbreak{}object = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = < a : int;\allowbreak{} b : int;\allowbreak{} >}\\ -\label{package-test+u+package+++ml-module-Type-type-lower+u+object}\codefragment{\begin{keyword}type\end{keyword} - 'a lower\_\allowbreak{}object = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = < a : int;\allowbreak{} b : int;\allowbreak{} .\allowbreak{}.\allowbreak{} >}\\ -\label{package-test+u+package+++ml-module-Type-type-poly+u+object}\codefragment{\begin{keyword}type\end{keyword} - 'a poly\_\allowbreak{}object = \begin{type-var}'a\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = < a : a.\allowbreak{} \begin{type-var}'a\end{type-var} -;\allowbreak{} >}\\ -\label{package-test+u+package+++ml-module-Type-type-double+u+constrained}\codefragment{\begin{keyword}type\end{keyword} - ('a,\allowbreak{} 'b) double\_\allowbreak{}constrained = \begin{type-var}'a\end{type-var} - * \begin{type-var}'b\end{type-var} - \begin{keyword}constraint\end{keyword} - \begin{type-var}'a\end{type-var} - = int \begin{keyword}constraint\end{keyword} - \begin{type-var}'b\end{type-var} - = unit}\\ -\label{package-test+u+package+++ml-module-Type-type-as+u+}\codefragment{\begin{keyword}type\end{keyword} - as\_\allowbreak{} = int \begin{keyword}as\end{keyword} - 'a * \begin{type-var}'a\end{type-var} -}\\ -\label{package-test+u+package+++ml-module-Type-type-extensible}\codefragment{\begin{keyword}type\end{keyword} - extensible = .\allowbreak{}.\allowbreak{}}\\ -\codefragment{\begin{keyword}type\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-type-extensible]{\inlinecode{extensible}} += }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\codefragment{| \begin{extension}Extension\end{extension} -}\label{package-test+u+package+++ml-module-Type-extension-Extension}& Documentation for \hyperref[package-test+u+package+++ml-module-Type-extension-Extension]{\inlinecode{\inlinecode{Extension}}[p\pageref*{package-test+u+package+++ml-module-Type-extension-Extension}]}.\\ -\codefragment{| \begin{extension}Another\_\allowbreak{}extension\end{extension} -}\label{package-test+u+package+++ml-module-Type-extension-Another+u+extension}& Documentation for \hyperref[package-test+u+package+++ml-module-Type-extension-Another+u+extension]{\inlinecode{\inlinecode{Another\_\allowbreak{}extension}}[p\pageref*{package-test+u+package+++ml-module-Type-extension-Another+u+extension}]}.\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-type-mutually}\codefragment{\begin{keyword}type\end{keyword} - mutually = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}A\end{constructor} - \begin{keyword}of\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-type-recursive]{\inlinecode{recursive}}}\label{package-test+u+package+++ml-module-Type-type-mutually.A}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-type-recursive}\codefragment{\begin{keyword}and\end{keyword} - recursive = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{longtable}[l]{p{1.000\textwidth}}\codefragment{| \begin{constructor}B\end{constructor} - \begin{keyword}of\end{keyword} - \hyperref[package-test+u+package+++ml-module-Type-type-mutually]{\inlinecode{mutually}}}\label{package-test+u+package+++ml-module-Type-type-recursive.B}\\ -\end{longtable}% -}\label{package-test+u+package+++ml-module-Type-exception-Foo}\codefragment{\begin{keyword}exception\end{keyword} - \begin{exception}Foo\end{exception} - \begin{keyword}of\end{keyword} - int * int}\\ +\ocamlcodefragment{\ocamltag{keyword}{end}}\\ +\label{package-test+u+package+++ml-module-Type-type-module+u+}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{} = (\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Type-module-type-X]{\ocamlinlinecode{X}})}\\ +\label{package-test+u+package+++ml-module-Type-type-module+u+substitution}\ocamlcodefragment{\ocamltag{keyword}{type} module\_\allowbreak{}substitution = (\ocamltag{keyword}{module} \hyperref[package-test+u+package+++ml-module-Type-module-type-X]{\ocamlinlinecode{X}} \ocamltag{keyword}{with} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Type-module-type-X-type-t]{\ocamlinlinecode{t}} = int \ocamltag{keyword}{and} \ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Type-module-type-X-type-u]{\ocamlinlinecode{u}} = unit)}\\ +\label{package-test+u+package+++ml-module-Type-type-covariant}\ocamlcodefragment{\ocamltag{keyword}{type} +'a covariant}\\ +\label{package-test+u+package+++ml-module-Type-type-contravariant}\ocamlcodefragment{\ocamltag{keyword}{type} -'a contravariant}\\ +\label{package-test+u+package+++ml-module-Type-type-bivariant}\ocamlcodefragment{\ocamltag{keyword}{type} \_\allowbreak{} bivariant = int}\\ +\label{package-test+u+package+++ml-module-Type-type-binary}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) binary}\\ +\label{package-test+u+package+++ml-module-Type-type-using+u+binary}\ocamlcodefragment{\ocamltag{keyword}{type} using\_\allowbreak{}binary = (int,\allowbreak{} int) \hyperref[package-test+u+package+++ml-module-Type-type-binary]{\ocamlinlinecode{binary}}}\\ +\label{package-test+u+package+++ml-module-Type-type-name}\ocamlcodefragment{\ocamltag{keyword}{type} 'custom name}\\ +\label{package-test+u+package+++ml-module-Type-type-constrained}\ocamlcodefragment{\ocamltag{keyword}{type} 'a constrained = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int}\\ +\label{package-test+u+package+++ml-module-Type-type-exact+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [ `A | `B of int ]}\\ +\label{package-test+u+package+++ml-module-Type-type-lower+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> `A | `B of int ]}\\ +\label{package-test+u+package+++ml-module-Type-type-any+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a any\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [> ]}\\ +\label{package-test+u+package+++ml-module-Type-type-upper+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a upper\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< `A | `B of int ]}\\ +\label{package-test+u+package+++ml-module-Type-type-named+u+variant}\ocamlcodefragment{\ocamltag{keyword}{type} 'a named\_\allowbreak{}variant = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = [< \hyperref[package-test+u+package+++ml-module-Type-type-polymorphic+u+variant]{\ocamlinlinecode{polymorphic\_\allowbreak{}variant}} ]}\\ +\label{package-test+u+package+++ml-module-Type-type-exact+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a exact\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int;\allowbreak{} b : int;\allowbreak{} >}\\ +\label{package-test+u+package+++ml-module-Type-type-lower+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a lower\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : int;\allowbreak{} b : int;\allowbreak{} .\allowbreak{}.\allowbreak{} >}\\ +\label{package-test+u+package+++ml-module-Type-type-poly+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} 'a poly\_\allowbreak{}object = \ocamltag{type-var}{'a} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = < a : a.\allowbreak{} \ocamltag{type-var}{'a};\allowbreak{} >}\\ +\label{package-test+u+package+++ml-module-Type-type-double+u+constrained}\ocamlcodefragment{\ocamltag{keyword}{type} ('a,\allowbreak{} 'b) double\_\allowbreak{}constrained = \ocamltag{type-var}{'a} * \ocamltag{type-var}{'b} \ocamltag{keyword}{constraint} \ocamltag{type-var}{'a} = int \ocamltag{keyword}{constraint} \ocamltag{type-var}{'b} = unit}\\ +\label{package-test+u+package+++ml-module-Type-type-as+u+}\ocamlcodefragment{\ocamltag{keyword}{type} as\_\allowbreak{} = int \ocamltag{keyword}{as} 'a * \ocamltag{type-var}{'a}}\\ +\label{package-test+u+package+++ml-module-Type-type-extensible}\ocamlcodefragment{\ocamltag{keyword}{type} extensible = .\allowbreak{}.\allowbreak{}}\\ +\ocamlcodefragment{\ocamltag{keyword}{type} \hyperref[package-test+u+package+++ml-module-Type-type-extensible]{\ocamlinlinecode{extensible}} += }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{0.500\textwidth}p{0.500\textwidth}}\ocamlcodefragment{| \ocamltag{extension}{Extension}}\label{package-test+u+package+++ml-module-Type-extension-Extension}& Documentation for \hyperref[package-test+u+package+++ml-module-Type-extension-Extension]{\ocamlinlinecode{\ocamlinlinecode{Extension}}[p\pageref*{package-test+u+package+++ml-module-Type-extension-Extension}]}.\\ +\ocamlcodefragment{| \ocamltag{extension}{Another\_\allowbreak{}extension}}\label{package-test+u+package+++ml-module-Type-extension-Another+u+extension}& Documentation for \hyperref[package-test+u+package+++ml-module-Type-extension-Another+u+extension]{\ocamlinlinecode{\ocamlinlinecode{Another\_\allowbreak{}extension}}[p\pageref*{package-test+u+package+++ml-module-Type-extension-Another+u+extension}]}.\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{type} mutually = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{A} \ocamltag{keyword}{of} \hyperref[package-test+u+package+++ml-module-Type-type-recursive]{\ocamlinlinecode{recursive}}}\label{package-test+u+package+++ml-module-Type-type-mutually.A}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{and} recursive = }{\setlength{\LTpre}{0pt}\setlength{\LTpost}{0pt}\begin{ocamllongtable}[l]{p{1.000\textwidth}}\ocamlcodefragment{| \ocamltag{constructor}{B} \ocamltag{keyword}{of} \hyperref[package-test+u+package+++ml-module-Type-type-mutually]{\ocamlinlinecode{mutually}}}\label{package-test+u+package+++ml-module-Type-type-recursive.B}\\ +\end{ocamllongtable}% +}\label{package-test+u+package+++ml-module-Type-exception-Foo}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{Foo} \ocamltag{keyword}{of} int * int}\\ diff --git a/test/latex/expect/test_package+ml/Val.tex b/test/latex/expect/test_package+ml/Val.tex index a5e0c333fb..edf25fefa3 100644 --- a/test/latex/expect/test_package+ml/Val.tex +++ b/test/latex/expect/test_package+ml/Val.tex @@ -1,11 +1,8 @@ -\section{Module \inlinecode{Val}}\label{package-test+u+package+++ml-module-Val}% -\label{package-test+u+package+++ml-module-Val-val-documented}\codefragment{\begin{keyword}val\end{keyword} - documented : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% +\section{Module \ocamlinlinecode{Val}}\label{package-test+u+package+++ml-module-Val}% +\label{package-test+u+package+++ml-module-Val-val-documented}\ocamlcodefragment{\ocamltag{keyword}{val} documented : unit}\begin{ocamlindent}Foo.\end{ocamlindent}% \medbreak -\label{package-test+u+package+++ml-module-Val-val-undocumented}\codefragment{\begin{keyword}val\end{keyword} - undocumented : unit}\\ -\label{package-test+u+package+++ml-module-Val-val-documented+u+above}\codefragment{\begin{keyword}val\end{keyword} - documented\_\allowbreak{}above : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% +\label{package-test+u+package+++ml-module-Val-val-undocumented}\ocamlcodefragment{\ocamltag{keyword}{val} undocumented : unit}\\ +\label{package-test+u+package+++ml-module-Val-val-documented+u+above}\ocamlcodefragment{\ocamltag{keyword}{val} documented\_\allowbreak{}above : unit}\begin{ocamlindent}Bar.\end{ocamlindent}% \medbreak diff --git a/test/latex/expect/test_package+ml/mld.tex b/test/latex/expect/test_package+ml/mld.tex index 65c1f99868..8c6ab9ce65 100644 --- a/test/latex/expect/test_package+ml/mld.tex +++ b/test/latex/expect/test_package+ml/mld.tex @@ -1,5 +1,5 @@ \section{Mld Page\label{mld-page}}\label{package-test+u+package+++ml-page-mld}% -This is an \inlinecode{.\allowbreak{}mld} file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. +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/latex/expect/visualizer.tex b/test/latex/expect/visualizer.tex index 1879fd259b..592dd290b7 100644 --- a/test/latex/expect/visualizer.tex +++ b/test/latex/expect/visualizer.tex @@ -17,21 +17,24 @@ \usepackage{lmodern} \usepackage[T1]{fontenc} -\newcommand{\codefragment}[1]{{\ttfamily\setlength{\parindent}{0cm}% +\newcommand{\ocamlcodefragment}[1]{{\ttfamily\setlength{\parindent}{0cm}% \raggedright#1}} -\newcommand{\inlinecode}[1]{{\ttfamily#1}} +\newcommand{\ocamlinlinecode}[1]{{\ttfamily#1}} \newcommand{\bold}[1]{{\bfseries#1}} \newenvironment{ocamlexception}{\bfseries}{} \newenvironment{ocamlextension}{\bfseries}{} -\newenvironment{keyword}{\bfseries}{} -\newenvironment{constructor}{\bfseries}{} -\newenvironment{type-var}{\itshape\ttfamily}{} +\newenvironment{ocamlkeyword}{\bfseries}{} + +\newenvironment{ocamlconstructor}{\bfseries}{} +\newenvironment{ocamltype-var}{\itshape\ttfamily}{} \newcommand{\ocamlhighlight}{\bfseries\uline} \newcommand{\ocamlerror}{\bfseries} \newcommand{\ocamlwarning}{\bfseries} +\newcommand{\ocamltag}[2]{\begin{ocaml#1}#2\end{ocaml#1}} + \definecolor{lightgray}{gray}{0.97} \definecolor{gray}{gray}{0.5} \newcommand{\ocamlcomment}{\color{gray}\normalfont\small} @@ -51,7 +54,7 @@ stringstyle=\ocamlstring, commentstyle=\ocamlcomment, keepspaces=true, - keywordstyle=\keyword, + keywordstyle=\ocamlkeyword, moredelim=[is][\ocamlhighlight]{<<}{>>}, moredelim=[s][\ocamlstring]{\{|}{|\}}, moredelim=[s][\ocamlstring]{\{delimiter|}{|delimiter\}},