From 6ddcac7a17c189bc6b769ad239c31a5ca0c9fec5 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Sun, 19 Dec 2021 15:51:54 +0300 Subject: [PATCH 01/38] add markup module Signed-off-by: lubegasimon --- src/markdown/markup.ml | 113 ++++++++++++++++++++++++++++++++++++++++ src/markdown/markup.mli | 62 ++++++++++++++++++++++ 2 files changed, 175 insertions(+) create mode 100644 src/markdown/markup.ml create mode 100644 src/markdown/markup.mli diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml new file mode 100644 index 0000000000..1b68a3e9be --- /dev/null +++ b/src/markdown/markup.ml @@ -0,0 +1,113 @@ +(* What we need in the markdown generator: + Special syntaxes: + - Pandoc's heading attributes +*) + +type inlines = + | String of string + | ConcatI of inlines * inlines + | Join of inlines * inlines + (** [Join] constructor is for joining [inlines] without spaces between them. *) + | Link of string * inlines + | Anchor of string + | Linebreak + | Nbsp + | Noop + +and blocks = + | ConcatB of blocks * blocks + | Block of inlines + | CodeBlock of string + | List of list_type * blocks list + | Raw_markup of string + | Block_separator + +and list_type = Ordered | Unordered + +let ordered_list bs = List (Ordered, bs) + +let unordered_list bs = List (Unordered, bs) + +let ( ++ ) left right = ConcatI (left, right) + +let join left right = Join (left, right) + +let blocks above below = ConcatB (above, below) + +let block_separator = Block_separator + +let text s = String s + +let line_break = Linebreak + +let nbsp = Nbsp + +let noop = Noop + +let bold i = Join (String "**", Join (i, String "**")) + +let italic i = Join (String "_", Join (i, String "_")) + +let subscript i = Join (String "", Join (i, String "")) + +let superscript i = Join (String "", Join (i, String "")) + +let code_span s = + if String.contains s '`' then "`` " ^ s ^ "``" else "`" ^ s ^ "`" + +let link ~href i = Link (href, i) + +let anchor' i = Anchor i + +let raw_markup s = Raw_markup s + +let paragraph i = Block i + +let code_block s = CodeBlock s + +let heading level i = + let make_hashes n = String.make n '#' in + let hashes = make_hashes level in + Block (String hashes ++ i) + +let pp_list_item fmt list_type (b : blocks) n pp_blocks = + match list_type with + | Unordered -> Format.fprintf fmt "- @[%a@]" pp_blocks b + | Ordered -> Format.fprintf fmt "%d. @[%a@]" (n + 1) pp_blocks b + +let rec pp_inlines fmt i = + match i with + | String s -> Format.fprintf fmt "%s" s + | ConcatI (left, right) -> + if left = noop then pp_inlines fmt right + else if right = noop then pp_inlines fmt left + else Format.fprintf fmt "%a %a" pp_inlines left pp_inlines right + | Join (left, right) -> + Format.fprintf fmt "%a%a" pp_inlines left pp_inlines right + | Link (href, i) -> Format.fprintf fmt "[%a](%s)" pp_inlines i href + | Anchor s -> Format.fprintf fmt "" s + | Linebreak -> Format.fprintf fmt "@\n" + | Nbsp -> Format.fprintf fmt "\u{00A0}" + | Noop -> () + +let rec pp_blocks fmt b = + match b with + | ConcatB (above, below) -> + if above = paragraph noop then pp_blocks fmt below + else if below = paragraph noop then pp_blocks fmt above + else Format.fprintf fmt "%a@\n@\n%a" pp_blocks above pp_blocks below + | Block i -> pp_inlines fmt i + | CodeBlock s -> Format.fprintf fmt "```@\n%s@\n```" s + | Block_separator -> Format.fprintf fmt "---" + | List (list_type, l) -> + let rec pp_list n l = + match l with + | [] -> () + | [ x ] -> pp_list_item fmt list_type x n pp_blocks + | x :: rest -> + pp_list_item fmt list_type x n pp_blocks; + Format.fprintf fmt "@\n@\n"; + pp_list (n + 1) rest + in + pp_list 0 l + | Raw_markup s -> Format.fprintf fmt "%s" s diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli new file mode 100644 index 0000000000..ace10d4238 --- /dev/null +++ b/src/markdown/markup.mli @@ -0,0 +1,62 @@ +(** The goal of this module is to allow to describe a markdown document and + to print it. + A markdown document is composed of [blocks]. *) + +type inlines +(** Inlines elements are rendered one after the other, separated by spaces, + but not by empty line. *) + +val ( ++ ) : inlines -> inlines -> inlines +(** Combine inlines. *) + +val join : inlines -> inlines -> inlines + +type blocks +(** A block is composed of [inlines]. Blocks are separated by an empty line. *) + +val ordered_list : blocks list -> blocks + +val unordered_list : blocks list -> blocks + +val blocks : blocks -> blocks -> blocks +(** Combine blocks. *) + +val block_separator : blocks +(** A horizontal line between a heading and the body. *) + +val text : string -> inlines +(** Some inline elements *) + +val line_break : inlines + +val nbsp : inlines + +val noop : inlines + +val bold : inlines -> inlines + +val italic : inlines -> inlines + +val superscript : inlines -> inlines + +val subscript : inlines -> inlines + +val link : href:string -> inlines -> inlines +(** Arbitrary link. *) + +val anchor' : string -> inlines + +val raw_markup : string -> blocks + +val code_span : string -> string + +val paragraph : inlines -> blocks + +val code_block : string -> blocks + +val heading : int -> inlines -> blocks + +(* val pp_inlines : Format.formatter -> inlines -> unit *) + +val pp_blocks : Format.formatter -> blocks -> unit +(** Renders a markdown document. *) From c40ab7cf435583a0f311092519010bfd6a8da532 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Sun, 19 Dec 2021 15:54:06 +0300 Subject: [PATCH 02/38] add markdown generator Signed-off-by: lubegasimon --- src/markdown/dune | 6 + src/markdown/generator.ml | 278 +++++++++++++++++++++++++++++++++++++ src/markdown/generator.mli | 3 + src/markdown/link.ml | 33 +++++ src/odoc/bin/main.ml | 17 +++ src/odoc/dune | 2 +- src/odoc/markdown.ml | 11 ++ 7 files changed, 349 insertions(+), 1 deletion(-) create mode 100644 src/markdown/dune create mode 100644 src/markdown/generator.ml create mode 100644 src/markdown/generator.mli create mode 100644 src/markdown/link.ml create mode 100644 src/odoc/markdown.ml diff --git a/src/markdown/dune b/src/markdown/dune new file mode 100644 index 0000000000..16895dd483 --- /dev/null +++ b/src/markdown/dune @@ -0,0 +1,6 @@ +(library + (name odoc_markdown) + (public_name odoc.markdown) + (instrumentation + (backend bisect_ppx)) + (libraries odoc_model odoc_document)) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml new file mode 100644 index 0000000000..f4fa7c12cb --- /dev/null +++ b/src/markdown/generator.ml @@ -0,0 +1,278 @@ +open Odoc_document +open Types +open Doctree +open Link +open Markup + +let style (style : style) = + match style with + | `Bold -> bold + | `Italic | `Emphasis -> italic + | `Superscript -> superscript + | `Subscript -> subscript + +let make_hashes n = String.make n '#' + +type args = { generate_links : bool } + +let rec source_contains_text (s : Source.t) = + let inline_contains_text (i : Inline.t) = + let check_inline_desc (i : Inline.desc) = + match i with Text "" | Text " " -> false | Text _ | _ -> true + in + List.exists (fun { Inline.desc = d; _ } -> check_inline_desc d) i + in + let check_source (s : Source.token) = + match s with + | Source.Elt i -> inline_contains_text i + | Tag (_, s) -> source_contains_text s + in + List.exists check_source s + +let rec source_code (s : Source.t) args = + match s with + | [] -> noop + | h :: t -> ( + let continue s = + if source_contains_text s then source_code s args else noop + in + match h with + | Source.Elt i -> inline i args ++ continue t + | Tag (Some "arrow", _) -> + text "->" (* takes care of the Entity branch of Inline.t *) + | Tag (_, s) -> continue s ++ continue t) + +and inline (l : Inline.t) args = + match l with + | [] -> noop + | i :: rest -> ( + let continue i = if i = [] then noop else inline i args in + let cond then_clause else_clause = + if args.generate_links then then_clause else else_clause + in + match i.desc with + | Text "" | Text " " -> continue rest + | Text _ -> + let l, _, rest = + Doctree.Take.until l ~classify:(function + | { Inline.desc = Text s; _ } -> Accum [ s ] + | _ -> Stop_and_keep) + in + (*TODO: string trim here works but, I don't think it's appropriate. *) + text String.(concat "" l |> trim) ++ continue rest + | Entity _ -> noop + | Styled (sty, content) -> style sty (continue content) ++ continue rest + | Linebreak -> line_break ++ continue rest + | Link (href, content) -> + link ~href (inline content args) ++ continue rest + | InternalLink (Resolved (link', content)) -> + cond + (match link'.page.parent with + | Some _ -> continue content ++ continue rest + | None -> + link ~href:(make_hashes 1 ^ link'.anchor) (inline content args) + ++ continue rest) + (continue content ++ continue rest) + | InternalLink (Unresolved content) -> continue content ++ continue rest + | Source content -> source_code content args ++ continue rest + | Raw_markup (_, s) -> text s ++ continue rest) + +let rec blocks' (bs : blocks list) = + match bs with + | [] -> paragraph noop + | [ b ] -> b + | b :: rest -> blocks b (blocks' rest) + +let rec block (l : Block.t) args = + let noop = paragraph noop in + match l with + | [] -> noop + | b :: rest -> ( + let continue r = if r = [] then noop else block r args in + match b.desc with + | Inline i -> blocks (paragraph (inline i args)) (continue rest) + | Paragraph i -> blocks (paragraph (inline i args)) (continue rest) + | List (list_typ, l') -> + let f bs = + match list_typ with + | Unordered -> unordered_list bs + | Ordered -> ordered_list bs + in + blocks (f (List.map (fun b -> block b args) l')) (continue rest) + | Description _ -> + let descrs, _, rest = + Take.until l ~classify:(function + | { Block.desc = Description l; _ } -> Accum l + | _ -> Stop_and_keep) + in + let f i = + let key = inline i.Description.key args in + let def = + match i.Description.definition with + | [] -> text "" + | h :: _ -> ( + match h.desc with Inline i -> inline i args | _ -> text "") + in + paragraph (join (text "@") (join key (text ":")) ++ def) + in + blocks (blocks' (List.map f descrs)) (continue rest) + | Source content -> + blocks (paragraph (source_code content args)) (continue rest) + | Verbatim content -> blocks (code_block content) (continue rest) + | Raw_markup (_, s) -> blocks (raw_markup s) (continue rest)) + +let heading' { Heading.label; level; title } args = + let title = inline title args in + match label with + | Some _ -> ( + match level with + | 1 -> heading level title + | _ -> blocks (heading level title) block_separator) + | None -> paragraph title + +let inline_subpage = function + | `Inline | `Open | `Default -> true + | `Closed -> false + +let item_prop = text (make_hashes 6 ^ " ") + +let expansion_not_inlined url = not (should_inline url) + +let take_code l = + let c, _, rest = + Take.until l ~classify:(function + | DocumentedSrc.Code c -> Accum c + | DocumentedSrc.Alternative (Expansion e) -> + if expansion_not_inlined e.url then Accum e.summary + else Rec e.expansion + | _ -> Stop_and_keep) + in + (c, rest) + +let rec acc_text (l : Block.t) : string = + match l with + | [] -> "" + | h :: rest -> ( + match h.desc with Paragraph i -> inline_text i ^ acc_text rest | _ -> "") + +and inline_text (i : Inline.t) = + match i with + | [] -> "" + | h :: rest -> ( + match h.desc with + | Text s -> s ^ inline_text rest + | Source s -> + let rec source_text (s' : Source.t) = + match s' with + | [] -> "" + | t :: rest_t -> ( + match t with + | Elt i -> inline_text i ^ source_text rest_t + | _ -> "") + in + code_span (source_text s) + | _ -> "") + +let rec documented_src (l : DocumentedSrc.t) args nbsps = + let nbsps' = nbsps ++ (nbsp ++ nbsp) in + let noop = paragraph noop in + match l with + | [] -> noop + | line :: rest -> ( + let continue r = if r = [] then noop else documented_src r args nbsps in + match line with + | Code s -> + if source_contains_text s then + let c, rest = take_code l in + blocks + (paragraph (item_prop ++ nbsps' ++ source_code c args)) + (continue rest) + else noop + | Alternative _ -> continue rest + | Subpage p -> blocks (subpage p.content args nbsps') (continue rest) + | Documented _ | Nested _ -> + let lines, _, rest = + Take.until l ~classify:(function + | DocumentedSrc.Documented { code; doc; anchor; _ } -> + Accum [ (`D code, doc, anchor) ] + | DocumentedSrc.Nested { code; doc; anchor; _ } -> + Accum [ (`N code, doc, anchor) ] + | _ -> Stop_and_keep) + in + let f (content, doc, (anchor : Odoc_document.Url.t option)) = + let doc = + match doc with + | [] -> noop + | doc -> paragraph (text (acc_text doc)) + in + let content = + match content with + | `D code (* for record fields and polymorphic variants *) -> + paragraph + (item_prop ++ nbsps' ++ (nbsp ++ nbsp) ++ inline code args) + | `N l (* for constructors *) -> + let c, rest = take_code l in + blocks + (paragraph + (item_prop ++ nbsps' ++ (nbsp ++ nbsp) + ++ source_code c args)) + (continue rest) + in + let item = blocks content doc in + if args.generate_links then + let anchor = + match anchor with Some a -> a.anchor | None -> "" + in + blocks (paragraph (anchor' anchor)) item + else item + in + blocks (blocks' (List.map f lines)) (continue rest)) + +and subpage { title = _; header = _; items; url = _ } args nbsps = + let content = items in + let surround body = if content = [] then paragraph line_break else body in + surround @@ item content args nbsps + +and item (l : Item.t list) args nbsps = + let noop = paragraph noop in + match l with + | [] -> noop + | i :: rest -> ( + let continue r = if r = [] then noop else item r args nbsps in + match i with + | Text b -> blocks (block b args) (continue rest) + | Heading h -> blocks (heading' h args) (continue rest) + | Declaration { attr = _; anchor; content; doc } -> + let decl = documented_src content args nbsps in + let doc = + match doc with [] -> noop | doc -> paragraph (text (acc_text doc)) + in + let item' = blocks decl doc in + if args.generate_links then + let anchor = match anchor with Some x -> x.anchor | None -> "" in + blocks (blocks (paragraph (anchor' anchor)) item') (continue rest) + else blocks item' (continue rest) + | Include { content = { summary; status; content }; _ } -> + let d = + if inline_subpage status then item content args nbsps + else paragraph (source_code summary args) + in + blocks d (continue rest)) + +let page { Page.header; items; url; _ } args = + let blocks'' l = List.map (fun s -> paragraph (text s)) l |> blocks' in + blocks' + ([ blocks'' (for_printing url) ] + @ [ blocks (item header args (text "")) (item items args (text "")) ]) + +let rec subpage subp (args : args) = + let p = subp.Subpage.content in + if should_inline p.url then [] else [ render p args ] + +and render (p : Page.t) args = + let content fmt = Format.fprintf fmt "%a" pp_blocks (page p args) in + let children = + Utils.flatmap ~f:(fun sp -> subpage sp args) (Subpages.compute p) + in + let filename = as_filename p.url in + { Odoc_document.Renderer.filename; content; children } diff --git a/src/markdown/generator.mli b/src/markdown/generator.mli new file mode 100644 index 0000000000..121ddb061c --- /dev/null +++ b/src/markdown/generator.mli @@ -0,0 +1,3 @@ +type args = { generate_links : bool } + +val render : Odoc_document.Types.Page.t -> args -> Odoc_document.Renderer.page diff --git a/src/markdown/link.ml b/src/markdown/link.ml new file mode 100644 index 0000000000..25d81ebf37 --- /dev/null +++ b/src/markdown/link.ml @@ -0,0 +1,33 @@ +open Odoc_document + +let for_printing url = List.map snd @@ Url.Path.to_list url + +let segment_to_string (kind, name) = + match kind with + | `Module | `Page | `LeafPage | `Class -> name + | _ -> Format.asprintf "%a-%s" Odoc_document.Url.Path.pp_kind kind name + +let as_filename (url : Url.Path.t) = + let components = Url.Path.to_list url in + let dir, path = + Url.Path.split + ~is_dir:(function `Page -> `Always | _ -> `Never) + components + in + let dir = List.map segment_to_string dir in + let path = String.concat "." (List.map segment_to_string path) in + let str_path = String.concat Fpath.dir_sep (dir @ [ path ]) in + Fpath.(v str_path + ".md") + +let rec is_class_or_module_path (url : Url.Path.t) = + match url.kind with + | `Module | `LeafPage | `Page | `Class -> ( + match url.parent with + | None -> true + | Some url -> is_class_or_module_path url) + | _ -> false + +let should_inline x = not @@ is_class_or_module_path x + +let files_of_url url = + if is_class_or_module_path url then [ as_filename url ] else [] diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index f198ccd49c..536e3fc53e 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -572,6 +572,20 @@ module Odoc_latex = Make_renderer (struct Term.(const f $ with_children) end) +module Odoc_markdown = Make_renderer (struct + type args = Markdown.args + + let renderer = Markdown.renderer + + let generate_links = + let doc = "Generate links in markdown." in + Arg.(value & flag (info ~doc [ "generate-links" ])) + + let extra_args = + let f generate_links = { Markdown.generate_links } in + Term.(const f $ generate_links) +end) + module Depends = struct module Compile = struct let list_dependencies input_file = @@ -720,6 +734,9 @@ let () = Odoc_html.process; Odoc_html.targets; Odoc_html.generate; + Odoc_markdown.process; + Odoc_markdown.targets; + Odoc_markdown.generate; Odoc_manpage.process; Odoc_manpage.targets; Odoc_manpage.generate; diff --git a/src/odoc/dune b/src/odoc/dune index 5ca7d74d2e..362638c66b 100644 --- a/src/odoc/dune +++ b/src/odoc/dune @@ -2,7 +2,7 @@ (name odoc_odoc) (public_name odoc.odoc) (libraries compiler-libs.common fpath odoc_html odoc_manpage odoc_latex - odoc_loader odoc_model odoc_xref2 tyxml unix) + odoc_markdown odoc_loader odoc_model odoc_xref2 tyxml unix) (instrumentation (backend bisect_ppx))) diff --git a/src/odoc/markdown.ml b/src/odoc/markdown.ml new file mode 100644 index 0000000000..d4bc30754b --- /dev/null +++ b/src/odoc/markdown.ml @@ -0,0 +1,11 @@ +open Odoc_document + +type args = { generate_links : bool } + +let render (args : args) (page : Odoc_document.Types.Page.t) : + Odoc_document.Renderer.page = + Odoc_markdown.Generator.render page { generate_links = args.generate_links } + +let files_of_url url = Odoc_markdown.Link.files_of_url url + +let renderer = { Renderer.name = "markdown"; render; files_of_url } From dc8604b0fdfb6b55b15d2b744a42bcb432be34f5 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Sun, 19 Dec 2021 15:55:39 +0300 Subject: [PATCH 03/38] add simple test module for ease PR review Signed-off-by: lubegasimon --- test/integration/markdown.t/test.mli | 123 +++++++++++++++++++++++++++ 1 file changed, 123 insertions(+) create mode 100644 test/integration/markdown.t/test.mli diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli new file mode 100644 index 0000000000..dac37c4e2e --- /dev/null +++ b/test/integration/markdown.t/test.mli @@ -0,0 +1,123 @@ +(** {1 This is a heading }*) + +(** {2:label This has a label}*) + +(** arrow (->) in a doc comment *) + +val concat : string -> string -> string + +(** {%html:foo:bar%} : a raw markup *) + +type t +(** Doc for [type t]. *) + +type a = t + +type y' + +module type Foo' = sig + type foo +end + +module Bar : sig + type bar +end + +module type Bar' = sig + type bar' +end + +module type Foo = sig + type foo + + include Bar' + + module type Foo' = sig + type foo' + + type days = Mon (** Docs for [days]. *) + + type num = [ `One (** Docs for [`One]*)] + end +end + +type other_names = { given : string; nickname : string } + +type name = { + fname : string; (** Docs for [fname] *) + lname : string; + others : other_names; +} + +(** {2:foo Label} *) + +(** {{:href} test_two } *) + +(** {{:href} {b test}} *) + +(** {{:href} test two foo } *) + +(** {{:href} **barz** } *) + +(** {v +verbatim +text +v} *) + +(** See if listness is preserved. *) + +(** This is an {i interface} with {b all} of the {e module system} features. + This documentation demonstrates: +- comment formatting +- unassociated comments +- documentation sections +- module system documentation including + {ol + {- submodules} + {- module aliases} + {- module types} + {- module type aliases} + {- modules with signatures} + {- modules with aliased signatures} +} + +A numbered list: ++ 3 ++ 2 ++ 1 + + David Sheets is the author. + @author David Sheets +*) + +(** The end foo end keyword in doc comment. *) +module Foo : sig + type foo + + type poly = [ `Mon | `Tue ] + + type name = { fname : string; lname : string } +end + +(** p1 *) + +(** p2 + + p3 + + {ul + {- a} + {- b} + } *) + +(** This is where I begin my thing from. *) + +(** {ol + {- one} + {- two} + } *) + +(** {ul + {- Mon} + {- Tue} + } *) From 1a934c6f7e9d0f28975c872b4ecdaabf157a03c4 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Sun, 19 Dec 2021 15:56:06 +0300 Subject: [PATCH 04/38] promote tests Signed-off-by: lubegasimon --- test/integration/markdown.t/run.t | 383 ++++++++++++++++++++++++++++++ 1 file changed, 383 insertions(+) create mode 100644 test/integration/markdown.t/run.t diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t new file mode 100644 index 0000000000..62233845b3 --- /dev/null +++ b/test/integration/markdown.t/run.t @@ -0,0 +1,383 @@ + $ ocamlc -c -bin-annot test.mli + $ odoc compile test.cmti + $ odoc link test.odoc + $ odoc markdown-generate test.odocl -o markdown + $ cat markdown/Test.md + Test + + Module Test + + # This is a heading + + ## This has a label + + --- + + arrow (->) in a doc comment + + ######     val concat : string -> string -> string + + foo:bar : a raw markup + + ######     type t + + Doc for `type t` + + ######     type a = t + + ######     type y' + + ######     module type Foo' = sig + + ######         type foo + + ######     end + + ######     module Bar : sig ... end + + ######     module type Bar' = sig + + ######         type bar' + + ######     end + + ######     module type Foo = sig + + ######         type foo + + ######         type bar' + + ######         module type Foo' = sig + + ######             type foo' + + ######             type days = + + ######                 | Mon + + Docs for `days` + + ######             type num = [ + + ######                 | `One + + Docs for `` `One`` + + ######             ] + + ######         end + + ######     end + + ######     type other_names = { + + ######         given : string ; + + ######         nickname : string ; + + ######     } + + ######     type name = { + + ######         fname : string ; + + Docs for `fname` + + ######         lname : string ; + + ######         others : other_names ; + + ######     } + + ## Label + + --- + + [test_two](href) + + [**test**](href) + + [test two foo](href) + + [**barz**](href) + + ``` + verbatim + text + ``` + + See if listness is preserved. + + This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: + + - comment formatting + + - unassociated comments + + - documentation sections + + - module system documentation including + + 1. submodules + + 2. module aliases + + 3. module types + + 4. module type aliases + + 5. modules with signatures + + 6. modules with aliased signatures + + A numbered list: + + 1. 3 + + 2. 2 + + 3. 1 + + David Sheets is the author. + + @author: David Sheets + + ######     module Foo : sig ... end + + The end foo end keyword in doc comment. + + p1 + + p2 + + p3 + + - a + + - b + + This is where I begin my thing from. + + 1. one + + 2. two + + - Mon + + - Tue + $ odoc markdown-generate test.odocl -o markdown --generate-links + $ cat markdown/Test.md + Test + + Module Test + + # This is a heading + + ## This has a label + + --- + + arrow (->) in a doc comment + + + + ######     val concat : string -> string -> string + + foo:bar : a raw markup + + + + ######     type t + + Doc for `type t` + + + + ######     type a = [t](#type-t) + + + + ######     type y' + + + + ######     module type Foo' = sig + + + + ######         type foo + + ######     end + + + + ######     module Bar : sig ... end + + + + ######     module type Bar' = sig + + + + ######         type bar' + + ######     end + + + + ######     module type Foo = sig + + + + ######         type foo + + + + ######         type bar' + + + + ######         module type Foo' = sig + + + + ######             type foo' + + + + ######             type days = + + + + ######                 | Mon + + Docs for `days` + + + + ######             type num = [ + + + + ######                 | `One + + Docs for `` `One`` + + ######             ] + + ######         end + + ######     end + + + + ######     type other_names = { + + + + ######         given : string ; + + + + ######         nickname : string ; + + ######     } + + + + ######     type name = { + + + + ######         fname : string ; + + Docs for `fname` + + + + ######         lname : string ; + + + + ######         others : [other_names](#type-other_names) ; + + ######     } + + ## Label + + --- + + [test_two](href) + + [**test**](href) + + [test two foo](href) + + [**barz**](href) + + ``` + verbatim + text + ``` + + See if listness is preserved. + + This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: + + - comment formatting + + - unassociated comments + + - documentation sections + + - module system documentation including + + 1. submodules + + 2. module aliases + + 3. module types + + 4. module type aliases + + 5. modules with signatures + + 6. modules with aliased signatures + + A numbered list: + + 1. 3 + + 2. 2 + + 3. 1 + + David Sheets is the author. + + @author: David Sheets + + + + ######     module Foo : sig ... end + + The end foo end keyword in doc comment. + + p1 + + p2 + + p3 + + - a + + - b + + This is where I begin my thing from. + + 1. one + + 2. two + + - Mon + + - Tue From 508704e05c9ef180bf33dd903dc8efc3d12e5a17 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Wed, 5 Jan 2022 22:22:26 +0300 Subject: [PATCH 05/38] some code improvements Signed-off-by: lubegasimon --- src/markdown/generator.ml | 77 ++++++++++++++++++--------------------- src/markdown/markup.mli | 2 - 2 files changed, 36 insertions(+), 43 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index f4fa7c12cb..969ead410d 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -47,9 +47,6 @@ and inline (l : Inline.t) args = | [] -> noop | i :: rest -> ( let continue i = if i = [] then noop else inline i args in - let cond then_clause else_clause = - if args.generate_links then then_clause else else_clause - in match i.desc with | Text "" | Text " " -> continue rest | Text _ -> @@ -58,21 +55,20 @@ and inline (l : Inline.t) args = | { Inline.desc = Text s; _ } -> Accum [ s ] | _ -> Stop_and_keep) in - (*TODO: string trim here works but, I don't think it's appropriate. *) text String.(concat "" l |> trim) ++ continue rest | Entity _ -> noop - | Styled (sty, content) -> style sty (continue content) ++ continue rest + | Styled (styl, content) -> style styl (continue content) ++ continue rest | Linebreak -> line_break ++ continue rest | Link (href, content) -> link ~href (inline content args) ++ continue rest | InternalLink (Resolved (link', content)) -> - cond - (match link'.page.parent with + if args.generate_links then + match link'.page.parent with | Some _ -> continue content ++ continue rest | None -> link ~href:(make_hashes 1 ^ link'.anchor) (inline content args) - ++ continue rest) - (continue content ++ continue rest) + ++ continue rest + else continue content ++ continue rest | InternalLink (Unresolved content) -> continue content ++ continue rest | Source content -> source_code content args ++ continue rest | Raw_markup (_, s) -> text s ++ continue rest) @@ -121,34 +117,6 @@ let rec block (l : Block.t) args = | Verbatim content -> blocks (code_block content) (continue rest) | Raw_markup (_, s) -> blocks (raw_markup s) (continue rest)) -let heading' { Heading.label; level; title } args = - let title = inline title args in - match label with - | Some _ -> ( - match level with - | 1 -> heading level title - | _ -> blocks (heading level title) block_separator) - | None -> paragraph title - -let inline_subpage = function - | `Inline | `Open | `Default -> true - | `Closed -> false - -let item_prop = text (make_hashes 6 ^ " ") - -let expansion_not_inlined url = not (should_inline url) - -let take_code l = - let c, _, rest = - Take.until l ~classify:(function - | DocumentedSrc.Code c -> Accum c - | DocumentedSrc.Alternative (Expansion e) -> - if expansion_not_inlined e.url then Accum e.summary - else Rec e.expansion - | _ -> Stop_and_keep) - in - (c, rest) - let rec acc_text (l : Block.t) : string = match l with | [] -> "" @@ -174,8 +142,21 @@ and inline_text (i : Inline.t) = | _ -> "") let rec documented_src (l : DocumentedSrc.t) args nbsps = - let nbsps' = nbsps ++ (nbsp ++ nbsp) in let noop = paragraph noop in + let nbsps' = nbsps ++ (nbsp ++ nbsp) in + let item_prop = text (make_hashes 6 ^ " ") in + let take_code l = + let c, _, rest = + let expansion_not_inlined url = not (should_inline url) in + Take.until l ~classify:(function + | DocumentedSrc.Code c -> Accum c + | DocumentedSrc.Alternative (Expansion e) -> + if expansion_not_inlined e.url then Accum e.summary + else Rec e.expansion + | _ -> Stop_and_keep) + in + (c, rest) + in match l with | [] -> noop | line :: rest -> ( @@ -230,8 +211,8 @@ let rec documented_src (l : DocumentedSrc.t) args nbsps = and subpage { title = _; header = _; items; url = _ } args nbsps = let content = items in - let surround body = if content = [] then paragraph line_break else body in - surround @@ item content args nbsps + let subpage' body = if content = [] then paragraph line_break else body in + subpage' @@ item content args nbsps and item (l : Item.t list) args nbsps = let noop = paragraph noop in @@ -241,7 +222,17 @@ and item (l : Item.t list) args nbsps = let continue r = if r = [] then noop else item r args nbsps in match i with | Text b -> blocks (block b args) (continue rest) - | Heading h -> blocks (heading' h args) (continue rest) + | Heading { Heading.label; level; title } -> + let heading' = + let title = inline title args in + match label with + | Some _ -> ( + match level with + | 1 -> heading level title + | _ -> blocks (heading level title) block_separator) + | None -> paragraph title + in + blocks heading' (continue rest) | Declaration { attr = _; anchor; content; doc } -> let decl = documented_src content args nbsps in let doc = @@ -253,6 +244,10 @@ and item (l : Item.t list) args nbsps = blocks (blocks (paragraph (anchor' anchor)) item') (continue rest) else blocks item' (continue rest) | Include { content = { summary; status; content }; _ } -> + let inline_subpage = function + | `Inline | `Open | `Default -> true + | `Closed -> false + in let d = if inline_subpage status then item content args nbsps else paragraph (source_code summary args) diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index ace10d4238..a10de4f88c 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -56,7 +56,5 @@ val code_block : string -> blocks val heading : int -> inlines -> blocks -(* val pp_inlines : Format.formatter -> inlines -> unit *) - val pp_blocks : Format.formatter -> blocks -> unit (** Renders a markdown document. *) From 06c6159b6f5bd3a7554a9eea9f65c8b0281c6dc1 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Tue, 18 Jan 2022 16:12:48 +0100 Subject: [PATCH 06/38] Fix path handling This changed upstream and is broken since a rebase. --- src/markdown/link.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/markdown/link.ml b/src/markdown/link.ml index 25d81ebf37..097534b239 100644 --- a/src/markdown/link.ml +++ b/src/markdown/link.ml @@ -11,7 +11,7 @@ let as_filename (url : Url.Path.t) = let components = Url.Path.to_list url in let dir, path = Url.Path.split - ~is_dir:(function `Page -> `Always | _ -> `Never) + ~is_dir:(function `Page -> `IfNotLast | _ -> `Never) components in let dir = List.map segment_to_string dir in From 6021e82d5add19055ab0fa5b263b8c96a3ae0307 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Tue, 18 Jan 2022 16:54:27 +0100 Subject: [PATCH 07/38] Improve indentation of headings - Use an incrementing integer for better control - Avoid putting a normal space between each nbsps --- src/markdown/generator.ml | 62 +++++++++----- src/markdown/markup.ml | 4 - src/markdown/markup.mli | 2 - test/integration/markdown.t/run.t | 132 +++++++++++++++--------------- 4 files changed, 107 insertions(+), 93 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 969ead410d..4bbf57a006 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -4,6 +4,15 @@ open Doctree open Link open Markup +(** Make a new string by copying the given string [n] times. *) +let string_repeat n s = + let s_len = String.length s in + let b = Bytes.create (s_len * n) in + for i = 0 to n - 1 do + Bytes.unsafe_blit_string s 0 b (i * s_len) s_len + done; + Bytes.unsafe_to_string b + let style (style : style) = match style with | `Bold -> bold @@ -11,8 +20,6 @@ let style (style : style) = | `Superscript -> superscript | `Subscript -> subscript -let make_hashes n = String.make n '#' - type args = { generate_links : bool } let rec source_contains_text (s : Source.t) = @@ -66,7 +73,7 @@ and inline (l : Inline.t) args = match link'.page.parent with | Some _ -> continue content ++ continue rest | None -> - link ~href:(make_hashes 1 ^ link'.anchor) (inline content args) + link ~href:("#" ^ link'.anchor) (inline content args) ++ continue rest else continue content ++ continue rest | InternalLink (Unresolved content) -> continue content ++ continue rest @@ -141,10 +148,22 @@ and inline_text (i : Inline.t) = code_span (source_text s) | _ -> "") -let rec documented_src (l : DocumentedSrc.t) args nbsps = +(** Generates the 6-heading used to differentiate items. Non-breaking spaces + are inserted just before the text, to simulate indentation depending on + [nesting_level]. + {v + ######Text + v} *) +let item_heading nesting_level content = + let pre_hash = text (String.make 6 '#') + and pre_nbsp = + if nesting_level = 0 then noop + else text (string_repeat (nesting_level * 2) "\u{A0}") + in + paragraph (pre_hash ++ pre_nbsp ++ content) + +let rec documented_src (l : DocumentedSrc.t) args nesting_level = let noop = paragraph noop in - let nbsps' = nbsps ++ (nbsp ++ nbsp) in - let item_prop = text (make_hashes 6 ^ " ") in let take_code l = let c, _, rest = let expansion_not_inlined url = not (should_inline url) in @@ -160,17 +179,20 @@ let rec documented_src (l : DocumentedSrc.t) args nbsps = match l with | [] -> noop | line :: rest -> ( - let continue r = if r = [] then noop else documented_src r args nbsps in + let continue r = + if r = [] then noop else documented_src r args nesting_level + in match line with | Code s -> if source_contains_text s then let c, rest = take_code l in blocks - (paragraph (item_prop ++ nbsps' ++ source_code c args)) + (item_heading nesting_level (source_code c args)) (continue rest) else noop | Alternative _ -> continue rest - | Subpage p -> blocks (subpage p.content args nbsps') (continue rest) + | Subpage p -> + blocks (subpage p.content args (nesting_level + 1)) (continue rest) | Documented _ | Nested _ -> let lines, _, rest = Take.until l ~classify:(function @@ -187,16 +209,14 @@ let rec documented_src (l : DocumentedSrc.t) args nbsps = | doc -> paragraph (text (acc_text doc)) in let content = + let nesting_level = nesting_level + 1 in match content with | `D code (* for record fields and polymorphic variants *) -> - paragraph - (item_prop ++ nbsps' ++ (nbsp ++ nbsp) ++ inline code args) + item_heading nesting_level (inline code args) | `N l (* for constructors *) -> let c, rest = take_code l in blocks - (paragraph - (item_prop ++ nbsps' ++ (nbsp ++ nbsp) - ++ source_code c args)) + (item_heading nesting_level (source_code c args)) (continue rest) in let item = blocks content doc in @@ -209,17 +229,17 @@ let rec documented_src (l : DocumentedSrc.t) args nbsps = in blocks (blocks' (List.map f lines)) (continue rest)) -and subpage { title = _; header = _; items; url = _ } args nbsps = +and subpage { title = _; header = _; items; url = _ } args nesting_level = let content = items in let subpage' body = if content = [] then paragraph line_break else body in - subpage' @@ item content args nbsps + subpage' @@ item content args nesting_level -and item (l : Item.t list) args nbsps = +and item (l : Item.t list) args nesting_level = let noop = paragraph noop in match l with | [] -> noop | i :: rest -> ( - let continue r = if r = [] then noop else item r args nbsps in + let continue r = if r = [] then noop else item r args nesting_level in match i with | Text b -> blocks (block b args) (continue rest) | Heading { Heading.label; level; title } -> @@ -234,7 +254,7 @@ and item (l : Item.t list) args nbsps = in blocks heading' (continue rest) | Declaration { attr = _; anchor; content; doc } -> - let decl = documented_src content args nbsps in + let decl = documented_src content args nesting_level in let doc = match doc with [] -> noop | doc -> paragraph (text (acc_text doc)) in @@ -249,7 +269,7 @@ and item (l : Item.t list) args nbsps = | `Closed -> false in let d = - if inline_subpage status then item content args nbsps + if inline_subpage status then item content args nesting_level else paragraph (source_code summary args) in blocks d (continue rest)) @@ -258,7 +278,7 @@ let page { Page.header; items; url; _ } args = let blocks'' l = List.map (fun s -> paragraph (text s)) l |> blocks' in blocks' ([ blocks'' (for_printing url) ] - @ [ blocks (item header args (text "")) (item items args (text "")) ]) + @ [ blocks (item header args 0) (item items args 0) ]) let rec subpage subp (args : args) = let p = subp.Subpage.content in diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 1b68a3e9be..896a2dce88 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -11,7 +11,6 @@ type inlines = | Link of string * inlines | Anchor of string | Linebreak - | Nbsp | Noop and blocks = @@ -40,8 +39,6 @@ let text s = String s let line_break = Linebreak -let nbsp = Nbsp - let noop = Noop let bold i = Join (String "**", Join (i, String "**")) @@ -87,7 +84,6 @@ let rec pp_inlines fmt i = | Link (href, i) -> Format.fprintf fmt "[%a](%s)" pp_inlines i href | Anchor s -> Format.fprintf fmt "" s | Linebreak -> Format.fprintf fmt "@\n" - | Nbsp -> Format.fprintf fmt "\u{00A0}" | Noop -> () let rec pp_blocks fmt b = diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index a10de4f88c..1c4fff4c02 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -29,8 +29,6 @@ val text : string -> inlines val line_break : inlines -val nbsp : inlines - val noop : inlines val bold : inlines -> inlines diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 62233845b3..9a203c02db 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -15,79 +15,79 @@ arrow (->) in a doc comment - ######     val concat : string -> string -> string + ###### val concat : string -> string -> string foo:bar : a raw markup - ######     type t + ###### type t Doc for `type t` - ######     type a = t + ###### type a = t - ######     type y' + ###### type y' - ######     module type Foo' = sig + ###### module type Foo' = sig - ######         type foo + ######    type foo - ######     end + ###### end - ######     module Bar : sig ... end + ###### module Bar : sig ... end - ######     module type Bar' = sig + ###### module type Bar' = sig - ######         type bar' + ######    type bar' - ######     end + ###### end - ######     module type Foo = sig + ###### module type Foo = sig - ######         type foo + ######    type foo - ######         type bar' + ######    type bar' - ######         module type Foo' = sig + ######    module type Foo' = sig - ######             type foo' + ######      type foo' - ######             type days = + ######      type days = - ######                 | Mon + ######        | Mon Docs for `days` - ######             type num = [ + ######      type num = [ - ######                 | `One + ######        | `One Docs for `` `One`` - ######             ] + ######      ] - ######         end + ######    end - ######     end + ###### end - ######     type other_names = { + ###### type other_names = { - ######         given : string ; + ######    given : string ; - ######         nickname : string ; + ######    nickname : string ; - ######     } + ###### } - ######     type name = { + ###### type name = { - ######         fname : string ; + ######    fname : string ; Docs for `fname` - ######         lname : string ; + ######    lname : string ; - ######         others : other_names ; + ######    others : other_names ; - ######     } + ###### } ## Label @@ -142,7 +142,7 @@ @author: David Sheets - ######     module Foo : sig ... end + ###### module Foo : sig ... end The end foo end keyword in doc comment. @@ -181,127 +181,127 @@ - ######     val concat : string -> string -> string + ###### val concat : string -> string -> string foo:bar : a raw markup - ######     type t + ###### type t Doc for `type t` - ######     type a = [t](#type-t) + ###### type a = [t](#type-t) - ######     type y' + ###### type y' - ######     module type Foo' = sig + ###### module type Foo' = sig - ######         type foo + ######    type foo - ######     end + ###### end - ######     module Bar : sig ... end + ###### module Bar : sig ... end - ######     module type Bar' = sig + ###### module type Bar' = sig - ######         type bar' + ######    type bar' - ######     end + ###### end - ######     module type Foo = sig + ###### module type Foo = sig - ######         type foo + ######    type foo - ######         type bar' + ######    type bar' - ######         module type Foo' = sig + ######    module type Foo' = sig - ######             type foo' + ######      type foo' - ######             type days = + ######      type days = - ######                 | Mon + ######        | Mon Docs for `days` - ######             type num = [ + ######      type num = [ - ######                 | `One + ######        | `One Docs for `` `One`` - ######             ] + ######      ] - ######         end + ######    end - ######     end + ###### end - ######     type other_names = { + ###### type other_names = { - ######         given : string ; + ######    given : string ; - ######         nickname : string ; + ######    nickname : string ; - ######     } + ###### } - ######     type name = { + ###### type name = { - ######         fname : string ; + ######    fname : string ; Docs for `fname` - ######         lname : string ; + ######    lname : string ; - ######         others : [other_names](#type-other_names) ; + ######    others : [other_names](#type-other_names) ; - ######     } + ###### } ## Label @@ -358,7 +358,7 @@ - ######     module Foo : sig ... end + ###### module Foo : sig ... end The end foo end keyword in doc comment. From 812289d24b1371b6ae097c58f487c942c7c79aa0 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 19 Jan 2022 16:44:00 +0100 Subject: [PATCH 08/38] Don't render alternatives as code --- src/markdown/generator.ml | 8 +++---- test/integration/markdown.t/run.t | 40 +++++++++++++++++++++---------- 2 files changed, 31 insertions(+), 17 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 4bbf57a006..e15cc77957 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -166,12 +166,8 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = let noop = paragraph noop in let take_code l = let c, _, rest = - let expansion_not_inlined url = not (should_inline url) in Take.until l ~classify:(function | DocumentedSrc.Code c -> Accum c - | DocumentedSrc.Alternative (Expansion e) -> - if expansion_not_inlined e.url then Accum e.summary - else Rec e.expansion | _ -> Stop_and_keep) in (c, rest) @@ -190,7 +186,9 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = (item_heading nesting_level (source_code c args)) (continue rest) else noop - | Alternative _ -> continue rest + | Alternative (Expansion { url; expansion; _ }) -> + if should_inline url then documented_src expansion args nesting_level + else continue rest | Subpage p -> blocks (subpage p.content args (nesting_level + 1)) (continue rest) | Documented _ | Nested _ -> diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 9a203c02db..8853b1fc75 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -27,27 +27,35 @@ ###### type y' - ###### module type Foo' = sig + ###### module type Foo' + + ###### = sig ######    type foo ###### end - ###### module Bar : sig ... end + ###### module Bar + + ###### module type Bar' - ###### module type Bar' = sig + ###### = sig ######    type bar' ###### end - ###### module type Foo = sig + ###### module type Foo + + ###### = sig ######    type foo ######    type bar' - ######    module type Foo' = sig + ######    module type Foo' + + ######    = sig ######      type foo' @@ -142,7 +150,7 @@ @author: David Sheets - ###### module Foo : sig ... end + ###### module Foo The end foo end keyword in doc comment. @@ -201,7 +209,9 @@ - ###### module type Foo' = sig + ###### module type Foo' + + ###### = sig @@ -211,11 +221,13 @@ - ###### module Bar : sig ... end + ###### module Bar - ###### module type Bar' = sig + ###### module type Bar' + + ###### = sig @@ -225,7 +237,9 @@ - ###### module type Foo = sig + ###### module type Foo + + ###### = sig @@ -237,7 +251,9 @@ - ######    module type Foo' = sig + ######    module type Foo' + + ######    = sig @@ -358,7 +374,7 @@ - ###### module Foo : sig ... end + ###### module Foo The end foo end keyword in doc comment. From e80d5a038117528ebbf2b692f591a9f4900a00dc Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 19 Jan 2022 17:04:04 +0100 Subject: [PATCH 09/38] Render 6-heading only for declarations Avoid adding headings for bits of code like '}' or 'end'. --- src/markdown/generator.ml | 56 ++++++++++++++++++++----------- src/markdown/markup.ml | 2 ++ src/markdown/markup.mli | 3 ++ test/integration/markdown.t/run.t | 44 ++++++++++++------------ 4 files changed, 64 insertions(+), 41 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index e15cc77957..1a45d36d92 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -162,16 +162,16 @@ let item_heading nesting_level content = in paragraph (pre_hash ++ pre_nbsp ++ content) +let take_code l = + let c, _, rest = + Take.until l ~classify:(function + | DocumentedSrc.Code c -> Accum c + | _ -> Stop_and_keep) + in + (c, rest) + let rec documented_src (l : DocumentedSrc.t) args nesting_level = let noop = paragraph noop in - let take_code l = - let c, _, rest = - Take.until l ~classify:(function - | DocumentedSrc.Code c -> Accum c - | _ -> Stop_and_keep) - in - (c, rest) - in match l with | [] -> noop | line :: rest -> ( @@ -182,10 +182,8 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = | Code s -> if source_contains_text s then let c, rest = take_code l in - blocks - (item_heading nesting_level (source_code c args)) - (continue rest) - else noop + paragraph (source_code c args) +++ continue rest + else continue rest | Alternative (Expansion { url; expansion; _ }) -> if should_inline url then documented_src expansion args nesting_level else continue rest @@ -251,16 +249,36 @@ and item (l : Item.t list) args nesting_level = | None -> paragraph title in blocks heading' (continue rest) - | Declaration { attr = _; anchor; content; doc } -> - let decl = documented_src content args nesting_level in + | Declaration { attr = _; anchor; content; doc } -> ( + (* + A declaration render like this: + + {v + + ###### + + + + + v} + *) let doc = match doc with [] -> noop | doc -> paragraph (text (acc_text doc)) + and anchor = + if args.generate_links then + let anchor = + match anchor with Some x -> x.anchor | None -> "" + in + paragraph (anchor' anchor) + else noop in - let item' = blocks decl doc in - if args.generate_links then - let anchor = match anchor with Some x -> x.anchor | None -> "" in - blocks (blocks (paragraph (anchor' anchor)) item') (continue rest) - else blocks item' (continue rest) + match take_code content with + | [], _ -> assert false (* Content doesn't begin with code ? *) + | begin_code, tl -> + anchor + +++ item_heading nesting_level (source_code begin_code args) + +++ documented_src tl args nesting_level + +++ doc +++ continue rest) | Include { content = { summary; status; content }; _ } -> let inline_subpage = function | `Inline | `Open | `Default -> true diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 896a2dce88..bd7134cee2 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -33,6 +33,8 @@ let join left right = Join (left, right) let blocks above below = ConcatB (above, below) +let ( +++ ) = blocks + let block_separator = Block_separator let text s = String s diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index 1c4fff4c02..16a56bb3f3 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -18,6 +18,9 @@ val ordered_list : blocks list -> blocks val unordered_list : blocks list -> blocks +val ( +++ ) : blocks -> blocks -> blocks +(** Alias for {!blocks} *) + val blocks : blocks -> blocks -> blocks (** Combine blocks. *) diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 8853b1fc75..b09d2ec723 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -29,25 +29,25 @@ ###### module type Foo' - ###### = sig + = sig ######    type foo - ###### end + end ###### module Bar ###### module type Bar' - ###### = sig + = sig ######    type bar' - ###### end + end ###### module type Foo - ###### = sig + = sig ######    type foo @@ -55,7 +55,7 @@ ######    module type Foo' - ######    = sig + = sig ######      type foo' @@ -71,11 +71,11 @@ Docs for `` `One`` - ######      ] + ] - ######    end + end - ###### end + end ###### type other_names = { @@ -83,7 +83,7 @@ ######    nickname : string ; - ###### } + } ###### type name = { @@ -95,7 +95,7 @@ ######    others : other_names ; - ###### } + } ## Label @@ -211,13 +211,13 @@ ###### module type Foo' - ###### = sig + = sig ######    type foo - ###### end + end @@ -227,19 +227,19 @@ ###### module type Bar' - ###### = sig + = sig ######    type bar' - ###### end + end ###### module type Foo - ###### = sig + = sig @@ -253,7 +253,7 @@ ######    module type Foo' - ######    = sig + = sig @@ -279,11 +279,11 @@ Docs for `` `One`` - ######      ] + ] - ######    end + end - ###### end + end @@ -297,7 +297,7 @@ ######    nickname : string ; - ###### } + } @@ -317,7 +317,7 @@ ######    others : [other_names](#type-other_names) ; - ###### } + } ## Label From 46e8f80dc0f96f0512fe682fb2352f41b3244fb3 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 19 Jan 2022 17:23:40 +0100 Subject: [PATCH 10/38] Improve test case --- test/integration/markdown.t/intf.mli | 47 +++ .../markdown.t/{test.mli => markup.mli} | 53 +-- test/integration/markdown.t/run.t | 338 ++++-------------- 3 files changed, 122 insertions(+), 316 deletions(-) create mode 100644 test/integration/markdown.t/intf.mli rename test/integration/markdown.t/{test.mli => markup.mli} (58%) diff --git a/test/integration/markdown.t/intf.mli b/test/integration/markdown.t/intf.mli new file mode 100644 index 0000000000..a55bbd5846 --- /dev/null +++ b/test/integration/markdown.t/intf.mli @@ -0,0 +1,47 @@ +(** Synopsis. + + Rest of preamble. *) + +(** Floating comment at the top. *) + +type t +(** Doc for [type t]. *) + +val x : t +(** Doc for [val x]. *) + +type a = t +(** Type alias *) + +(** Doc for [type b]. *) +type b = A (** Doc for [A]. *) | B (** Doc for [B]. *) + +type c = { a : int; (** Doc for [a]. *) b : int (** Doc for [b]. *) } +(** Doc for [type c]. *) + +val y : [ `One (** Doc for [`One]. *) | `Two (** Doc for [`Two]. *) ] +(** Polymorphic variant. *) + +(** Floating comment. *) + +val z : t -> (t -> t) -> foo:t -> ?bar:t -> [ `One of t ] -> t * t +(** Type complicated enough to be rendered differently. *) + +(** Outer doc for [M]. *) +module M : sig + (** Inner doc for [M]. *) + + type t +end + +module N : sig + (** Doc for [N]. *) + + type t +end + +module type S = sig + (** Doc for [S]. *) + + type t +end diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/markup.mli similarity index 58% rename from test/integration/markdown.t/test.mli rename to test/integration/markdown.t/markup.mli index dac37c4e2e..5644997de4 100644 --- a/test/integration/markdown.t/test.mli +++ b/test/integration/markdown.t/markup.mli @@ -4,51 +4,8 @@ (** arrow (->) in a doc comment *) -val concat : string -> string -> string - (** {%html:foo:bar%} : a raw markup *) -type t -(** Doc for [type t]. *) - -type a = t - -type y' - -module type Foo' = sig - type foo -end - -module Bar : sig - type bar -end - -module type Bar' = sig - type bar' -end - -module type Foo = sig - type foo - - include Bar' - - module type Foo' = sig - type foo' - - type days = Mon (** Docs for [days]. *) - - type num = [ `One (** Docs for [`One]*)] - end -end - -type other_names = { given : string; nickname : string } - -type name = { - fname : string; (** Docs for [fname] *) - lname : string; - others : other_names; -} - (** {2:foo Label} *) (** {{:href} test_two } *) @@ -90,15 +47,6 @@ A numbered list: @author David Sheets *) -(** The end foo end keyword in doc comment. *) -module Foo : sig - type foo - - type poly = [ `Mon | `Tue ] - - type name = { fname : string; lname : string } -end - (** p1 *) (** p2 @@ -121,3 +69,4 @@ end {- Mon} {- Tue} } *) + diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index b09d2ec723..6863d3e869 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -1,183 +1,129 @@ - $ ocamlc -c -bin-annot test.mli - $ odoc compile test.cmti - $ odoc link test.odoc - $ odoc markdown-generate test.odocl -o markdown - $ cat markdown/Test.md - Test + $ ocamlc -c -bin-annot intf.mli markup.mli + $ odoc compile intf.cmti + $ odoc compile markup.cmti + $ odoc link intf.odoc + $ odoc link markup.odoc + $ odoc markdown-generate intf.odocl -o markdown --generate-links + $ odoc markdown-generate markup.odocl -o markdown --generate-links + + $ find markdown + markdown + markdown/Intf.md + markdown/Markup.md + markdown/Intf.M.md + markdown/Intf.N.md + + $ cat markdown/Intf.md + Intf + + Module Intf + + Synopsis. + + Rest of preamble. + + Floating comment at the top. - Module Test - - # This is a heading - - ## This has a label - - --- - - arrow (->) in a doc comment - - ###### val concat : string -> string -> string - - foo:bar : a raw markup + ###### type t Doc for `type t` - ###### type a = t - - ###### type y' - - ###### module type Foo' - - = sig - - ######    type foo - - end - - ###### module Bar - - ###### module type Bar' - - = sig - - ######    type bar' - - end - - ###### module type Foo + - = sig + ###### val x : [t](#type-t) - ######    type foo + Doc for `val x` - ######    type bar' - - ######    module type Foo' - - = sig + - ######      type foo' + ###### type a = [t](#type-t) - ######      type days = + Type alias - ######        | Mon + - Docs for `days` + ###### type b = - ######      type num = [ + - ######        | `One + ######    | A - Docs for `` `One`` + Doc for `A` - ] + - end + ######    | B - end + Doc for `B` - ###### type other_names = { + Doc for `type b` - ######    given : string ; + - ######    nickname : string ; + ###### type c = { - } + - ###### type name = { + ######    a : int ; - ######    fname : string ; + Doc for `a` - Docs for `fname` + - ######    lname : string ; + ######    b : int ; - ######    others : other_names ; + Doc for `b` } - ## Label - - --- - - [test_two](href) - - [**test**](href) - - [test two foo](href) - - [**barz**](href) - - ``` - verbatim - text - ``` - - See if listness is preserved. - - This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: - - - comment formatting + Doc for `type c` - - unassociated comments - - - documentation sections + - - module system documentation including - - 1. submodules - - 2. module aliases - - 3. module types - - 4. module type aliases - - 5. modules with signatures - - 6. modules with aliased signatures + ###### val y : [ `One | `Two ] - A numbered list: + Polymorphic variant. - 1. 3 + Floating comment. - 2. 2 + - 3. 1 + ###### val z : [t](#type-t) -> ( [t](#type-t) -> [t](#type-t) ) -> foo : [t](#type-t) -> ? bar : [t](#type-t) -> [ `One of [t](#type-t) ] -> [t](#type-t) * [t](#type-t) - David Sheets is the author. + Type complicated enough to be rendered differently. - @author: David Sheets + - ###### module Foo + ###### module M - The end foo end keyword in doc comment. + Outer doc for `M` - p1 + - p2 + ###### module N - p3 + Doc for `N` - - a + - - b + ###### module type S - This is where I begin my thing from. + = sig - 1. one + - 2. two + ######    type t - - Mon + end - - Tue - $ odoc markdown-generate test.odocl -o markdown --generate-links - $ cat markdown/Test.md - Test + Doc for `S` + + $ cat markdown/Markup.md + Markup - Module Test + Module Markup # This is a heading @@ -187,138 +133,8 @@ arrow (->) in a doc comment - - - ###### val concat : string -> string -> string - foo:bar : a raw markup - - - ###### type t - - Doc for `type t` - - - - ###### type a = [t](#type-t) - - - - ###### type y' - - - - ###### module type Foo' - - = sig - - - - ######    type foo - - end - - - - ###### module Bar - - - - ###### module type Bar' - - = sig - - - - ######    type bar' - - end - - - - ###### module type Foo - - = sig - - - - ######    type foo - - - - ######    type bar' - - - - ######    module type Foo' - - = sig - - - - ######      type foo' - - - - ######      type days = - - - - ######        | Mon - - Docs for `days` - - - - ######      type num = [ - - - - ######        | `One - - Docs for `` `One`` - - ] - - end - - end - - - - ###### type other_names = { - - - - ######    given : string ; - - - - ######    nickname : string ; - - } - - - - ###### type name = { - - - - ######    fname : string ; - - Docs for `fname` - - - - ######    lname : string ; - - - - ######    others : [other_names](#type-other_names) ; - - } - ## Label --- @@ -372,12 +188,6 @@ @author: David Sheets - - - ###### module Foo - - The end foo end keyword in doc comment. - p1 p2 From cba655d3c7dfa4b1904579a16f5fa9cf99ca1476 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 19 Jan 2022 17:49:58 +0100 Subject: [PATCH 11/38] Take code from inlined expansions --- src/markdown/generator.ml | 25 ++++++++++++++++--------- test/integration/markdown.t/run.t | 4 +--- 2 files changed, 17 insertions(+), 12 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 1a45d36d92..d80dfd6dba 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -249,9 +249,9 @@ and item (l : Item.t list) args nesting_level = | None -> paragraph title in blocks heading' (continue rest) - | Declaration { attr = _; anchor; content; doc } -> ( + | Declaration { attr = _; anchor; content; doc } -> (* - A declaration render like this: + Declarations render like this: {v @@ -271,14 +271,21 @@ and item (l : Item.t list) args nesting_level = in paragraph (anchor' anchor) else noop + and begin_code, content = + match take_code content with + | [], _ -> assert false (* Content doesn't begin with code ? *) + | begin_code, Alternative (Expansion e) :: tl + when should_inline e.url -> + (* Take the code from inlined expansion. For example, to catch + [= sig]. *) + let e_code, e_tl = take_code e.expansion in + (begin_code @ e_code, e_tl @ tl) + | begin_code, content -> (begin_code, content) in - match take_code content with - | [], _ -> assert false (* Content doesn't begin with code ? *) - | begin_code, tl -> - anchor - +++ item_heading nesting_level (source_code begin_code args) - +++ documented_src tl args nesting_level - +++ doc +++ continue rest) + anchor + +++ item_heading nesting_level (source_code begin_code args) + +++ documented_src content args nesting_level + +++ doc +++ continue rest | Include { content = { summary; status; content }; _ } -> let inline_subpage = function | `Inline | `Open | `Default -> true diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 6863d3e869..c7ab9c2c80 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -108,9 +108,7 @@ - ###### module type S - - = sig + ###### module type S = sig From 91e7cb044d22a095e83744e6ec7e7a6858c3b0a2 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 19 Jan 2022 18:31:53 +0100 Subject: [PATCH 12/38] Render formatted code out of headings --- src/markdown/generator.ml | 69 ++++++++++++++++++++++++------- test/integration/markdown.t/run.t | 16 +++++-- 2 files changed, 65 insertions(+), 20 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index d80dfd6dba..3741106e3a 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -36,6 +36,27 @@ let rec source_contains_text (s : Source.t) = in List.exists check_source s +(** Split source code at the first [:] or [=]. *) +let source_take_until_punctuation code = + let rec is_punctuation s i = + if i >= String.length s then false + else + match s.[i] with + | ' ' -> is_punctuation s (i + 1) + | ':' | '=' -> true + | _ -> false + in + let is_punctuation i = + List.exists + (function + | { Inline.desc = Text s; _ } -> is_punctuation s 0 | _ -> false) + i + in + Take.until code ~classify:(function + | Source.Elt i as t -> + if is_punctuation i then Stop_and_accum ([ t ], None) else Accum [ t ] + | Tag (_, c) -> Rec c) + let rec source_code (s : Source.t) args = match s with | [] -> noop @@ -249,7 +270,7 @@ and item (l : Item.t list) args nesting_level = | None -> paragraph title in blocks heading' (continue rest) - | Declaration { attr = _; anchor; content; doc } -> + | Declaration { attr = _; anchor; content; doc } -> ( (* Declarations render like this: @@ -262,18 +283,8 @@ and item (l : Item.t list) args nesting_level = v} *) - let doc = - match doc with [] -> noop | doc -> paragraph (text (acc_text doc)) - and anchor = - if args.generate_links then - let anchor = - match anchor with Some x -> x.anchor | None -> "" - in - paragraph (anchor' anchor) - else noop - and begin_code, content = + let take_code_from_declaration content = match take_code content with - | [], _ -> assert false (* Content doesn't begin with code ? *) | begin_code, Alternative (Expansion e) :: tl when should_inline e.url -> (* Take the code from inlined expansion. For example, to catch @@ -282,10 +293,36 @@ and item (l : Item.t list) args nesting_level = (begin_code @ e_code, e_tl @ tl) | begin_code, content -> (begin_code, content) in - anchor - +++ item_heading nesting_level (source_code begin_code args) - +++ documented_src content args nesting_level - +++ doc +++ continue rest + let render_declaration ~anchor ~doc heading content = + let doc = + match doc with + | [] -> noop + | doc -> paragraph (text (acc_text doc)) + and anchor = + if args.generate_links then + let anchor = + match anchor with Some x -> x.Url.Anchor.anchor | None -> "" + in + paragraph (anchor' anchor) + else noop + in + anchor + +++ item_heading nesting_level (source_code heading args) + +++ content +++ doc +++ continue rest + in + match take_code_from_declaration content with + | code, [] -> + (* Declaration is only code, render formatted code. *) + let code, _, content = source_take_until_punctuation code in + let content = + if source_contains_text content then + paragraph (source_code content args) + else noop + in + render_declaration ~anchor ~doc code content + | code, content -> + render_declaration ~anchor ~doc code + (documented_src content args nesting_level)) | Include { content = { summary; status; content }; _ } -> let inline_subpage = function | `Inline | `Open | `Default -> true diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index c7ab9c2c80..cb1dc2597e 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -32,13 +32,17 @@ - ###### val x : [t](#type-t) + ###### val x : + + [t](#type-t) Doc for `val x` - ###### type a = [t](#type-t) + ###### type a = + + [t](#type-t) Type alias @@ -82,7 +86,9 @@ - ###### val y : [ `One | `Two ] + ###### val y : + + [ `One | `Two ] Polymorphic variant. @@ -90,7 +96,9 @@ - ###### val z : [t](#type-t) -> ( [t](#type-t) -> [t](#type-t) ) -> foo : [t](#type-t) -> ? bar : [t](#type-t) -> [ `One of [t](#type-t) ] -> [t](#type-t) * [t](#type-t) + ###### val z : + + [t](#type-t) -> ( [t](#type-t) -> [t](#type-t) ) -> foo : [t](#type-t) -> ? bar : [t](#type-t) -> [ `One of [t](#type-t) ] -> [t](#type-t) * [t](#type-t) Type complicated enough to be rendered differently. From 0d5e556b89a4ebc60af768817773d2d24e8b679d Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 19 Jan 2022 19:04:06 +0100 Subject: [PATCH 13/38] Render formatted code in quote blocks --- src/markdown/generator.ml | 2 +- src/markdown/markup.ml | 12 ++++++++++++ src/markdown/markup.mli | 2 ++ test/integration/markdown.t/run.t | 12 ++++++++---- 4 files changed, 23 insertions(+), 5 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 3741106e3a..bfa28986ef 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -316,7 +316,7 @@ and item (l : Item.t list) args nesting_level = let code, _, content = source_take_until_punctuation code in let content = if source_contains_text content then - paragraph (source_code content args) + quote_block (paragraph (source_code content args)) else noop in render_declaration ~anchor ~doc code content diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index bd7134cee2..5b66883750 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -20,6 +20,7 @@ and blocks = | List of list_type * blocks list | Raw_markup of string | Block_separator + | Prefixed_block of string * blocks (** Prefix every lines of blocks. *) and list_type = Ordered | Unordered @@ -64,11 +65,20 @@ let paragraph i = Block i let code_block s = CodeBlock s +let quote_block b = Prefixed_block ("> ", b) + let heading level i = let make_hashes n = String.make n '#' in let hashes = make_hashes level in Block (String hashes ++ i) +(** Every lines that [f] formats are prefixed and written in [sink]. + Inefficient. *) +let with_prefixed_formatter prefix sink f = + let s = Format.asprintf "%t" f in + String.split_on_char '\n' s + |> List.iter (fun l -> Format.fprintf sink "%s%s@\n" prefix l) + let pp_list_item fmt list_type (b : blocks) n pp_blocks = match list_type with | Unordered -> Format.fprintf fmt "- @[%a@]" pp_blocks b @@ -109,3 +119,5 @@ let rec pp_blocks fmt b = in pp_list 0 l | Raw_markup s -> Format.fprintf fmt "%s" s + | Prefixed_block (p, b) -> + with_prefixed_formatter p fmt (fun fmt -> pp_blocks fmt b) diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index 16a56bb3f3..ce78a8f807 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -55,6 +55,8 @@ val paragraph : inlines -> blocks val code_block : string -> blocks +val quote_block : blocks -> blocks + val heading : int -> inlines -> blocks val pp_blocks : Format.formatter -> blocks -> unit diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index cb1dc2597e..015d8228e5 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -34,7 +34,8 @@ ###### val x : - [t](#type-t) + > [t](#type-t) + Doc for `val x` @@ -42,7 +43,8 @@ ###### type a = - [t](#type-t) + > [t](#type-t) + Type alias @@ -88,7 +90,8 @@ ###### val y : - [ `One | `Two ] + > [ `One | `Two ] + Polymorphic variant. @@ -98,7 +101,8 @@ ###### val z : - [t](#type-t) -> ( [t](#type-t) -> [t](#type-t) ) -> foo : [t](#type-t) -> ? bar : [t](#type-t) -> [ `One of [t](#type-t) ] -> [t](#type-t) * [t](#type-t) + > [t](#type-t) -> ( [t](#type-t) -> [t](#type-t) ) -> foo : [t](#type-t) -> ? bar : [t](#type-t) -> [ `One of [t](#type-t) ] -> [t](#type-t) * [t](#type-t) + Type complicated enough to be rendered differently. From 0c45ebb9a1cc4baff0cc12b3679d8edde5c2db03 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Fri, 28 Jan 2022 10:50:59 +0100 Subject: [PATCH 14/38] Disable inlining of expansions We keep the inlining code for now, as it is partially used for other purposes (variants, records) and in case we'd want to add it back. --- src/markdown/link.ml | 12 ++---------- 1 file changed, 2 insertions(+), 10 deletions(-) diff --git a/src/markdown/link.ml b/src/markdown/link.ml index 097534b239..8bd3b16c5f 100644 --- a/src/markdown/link.ml +++ b/src/markdown/link.ml @@ -19,15 +19,7 @@ let as_filename (url : Url.Path.t) = let str_path = String.concat Fpath.dir_sep (dir @ [ path ]) in Fpath.(v str_path + ".md") -let rec is_class_or_module_path (url : Url.Path.t) = - match url.kind with - | `Module | `LeafPage | `Page | `Class -> ( - match url.parent with - | None -> true - | Some url -> is_class_or_module_path url) - | _ -> false - -let should_inline x = not @@ is_class_or_module_path x +let should_inline _ = false let files_of_url url = - if is_class_or_module_path url then [ as_filename url ] else [] + if should_inline url then [] else [ as_filename url ] From 749fead4c1048858b8c04430ef5230242fe19fc5 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 2 Feb 2022 11:40:46 +0100 Subject: [PATCH 15/38] Generate correct links to other pages Handle the InternalLink case correctly. --- src/markdown/generator.ml | 35 +++++++++++++++---------------- src/markdown/generator.mli | 7 ++++--- src/markdown/link.ml | 13 ++++++++++++ src/odoc/markdown.ml | 4 ++-- test/integration/markdown.t/run.t | 15 +++++-------- 5 files changed, 41 insertions(+), 33 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index bfa28986ef..63e2b34c8b 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -1,7 +1,6 @@ open Odoc_document open Types open Doctree -open Link open Markup (** Make a new string by copying the given string [n] times. *) @@ -20,7 +19,7 @@ let style (style : style) = | `Superscript -> superscript | `Subscript -> subscript -type args = { generate_links : bool } +type args = { base_path : Url.Path.t; generate_links : bool } let rec source_contains_text (s : Source.t) = let inline_contains_text (i : Inline.t) = @@ -89,13 +88,12 @@ and inline (l : Inline.t) args = | Linebreak -> line_break ++ continue rest | Link (href, content) -> link ~href (inline content args) ++ continue rest - | InternalLink (Resolved (link', content)) -> + | InternalLink (Resolved (url, content)) -> if args.generate_links then - match link'.page.parent with - | Some _ -> continue content ++ continue rest - | None -> - link ~href:("#" ^ link'.anchor) (inline content args) - ++ continue rest + link + ~href:(Link.href ~base_path:args.base_path url) + (inline content args) + ++ continue rest else continue content ++ continue rest | InternalLink (Unresolved content) -> continue content ++ continue rest | Source content -> source_code content args ++ continue rest @@ -206,7 +204,7 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = paragraph (source_code c args) +++ continue rest else continue rest | Alternative (Expansion { url; expansion; _ }) -> - if should_inline url then documented_src expansion args nesting_level + if Link.should_inline url then documented_src expansion args nesting_level else continue rest | Subpage p -> blocks (subpage p.content args (nesting_level + 1)) (continue rest) @@ -286,7 +284,7 @@ and item (l : Item.t list) args nesting_level = let take_code_from_declaration content = match take_code content with | begin_code, Alternative (Expansion e) :: tl - when should_inline e.url -> + when Link.should_inline e.url -> (* Take the code from inlined expansion. For example, to catch [= sig]. *) let e_code, e_tl = take_code e.expansion in @@ -334,20 +332,21 @@ and item (l : Item.t list) args nesting_level = in blocks d (continue rest)) -let page { Page.header; items; url; _ } args = +let page ~generate_links { Page.header; items; url; _ } = + let args = { base_path = url; generate_links } in let blocks'' l = List.map (fun s -> paragraph (text s)) l |> blocks' in blocks' - ([ blocks'' (for_printing url) ] + ([ blocks'' (Link.for_printing url) ] @ [ blocks (item header args 0) (item items args 0) ]) -let rec subpage subp (args : args) = +let rec subpage ~generate_links subp = let p = subp.Subpage.content in - if should_inline p.url then [] else [ render p args ] + if Link.should_inline p.url then [] else [ render ~generate_links p ] -and render (p : Page.t) args = - let content fmt = Format.fprintf fmt "%a" pp_blocks (page p args) in +and render ~generate_links (p : Page.t) = + let content fmt = Format.fprintf fmt "%a" pp_blocks (page ~generate_links p) in let children = - Utils.flatmap ~f:(fun sp -> subpage sp args) (Subpages.compute p) + Utils.flatmap ~f:(fun sp -> subpage ~generate_links sp) (Subpages.compute p) in - let filename = as_filename p.url in + let filename = Link.as_filename p.url in { Odoc_document.Renderer.filename; content; children } diff --git a/src/markdown/generator.mli b/src/markdown/generator.mli index 121ddb061c..4ee136c798 100644 --- a/src/markdown/generator.mli +++ b/src/markdown/generator.mli @@ -1,3 +1,4 @@ -type args = { generate_links : bool } - -val render : Odoc_document.Types.Page.t -> args -> Odoc_document.Renderer.page +val render : + generate_links:bool -> + Odoc_document.Types.Page.t -> + Odoc_document.Renderer.page diff --git a/src/markdown/link.ml b/src/markdown/link.ml index 8bd3b16c5f..be7592b814 100644 --- a/src/markdown/link.ml +++ b/src/markdown/link.ml @@ -19,6 +19,19 @@ let as_filename (url : Url.Path.t) = let str_path = String.concat Fpath.dir_sep (dir @ [ path ]) in Fpath.(v str_path + ".md") +let href ~base_path (url : Url.t) = + let anchor = match url.anchor with "" -> "" | anchor -> "#" ^ anchor in + if url.page = base_path then anchor + else + let root = Fpath.parent (as_filename base_path) + and path = as_filename url.page in + let path = + match Fpath.relativize ~root path with + | Some path -> path + | None -> assert false + in + Fpath.to_string path ^ anchor + let should_inline _ = false let files_of_url url = diff --git a/src/odoc/markdown.ml b/src/odoc/markdown.ml index d4bc30754b..d60ae1ff72 100644 --- a/src/odoc/markdown.ml +++ b/src/odoc/markdown.ml @@ -2,9 +2,9 @@ open Odoc_document type args = { generate_links : bool } -let render (args : args) (page : Odoc_document.Types.Page.t) : +let render { generate_links } (page : Odoc_document.Types.Page.t) : Odoc_document.Renderer.page = - Odoc_markdown.Generator.render page { generate_links = args.generate_links } + Odoc_markdown.Generator.render ~generate_links page let files_of_url url = Odoc_markdown.Link.files_of_url url diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 015d8228e5..3be0c2191e 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -10,8 +10,9 @@ markdown markdown/Intf.md markdown/Markup.md - markdown/Intf.M.md markdown/Intf.N.md + markdown/Intf.module-type-S.md + markdown/Intf.M.md $ cat markdown/Intf.md Intf @@ -108,25 +109,19 @@ - ###### module M + ###### module [M](Intf.M.md) Outer doc for `M` - ###### module N + ###### module [N](Intf.N.md) Doc for `N` - ###### module type S = sig - - - - ######    type t - - end + ###### module type [S](Intf.module-type-S.md) Doc for `S` From d2c2dcaf81877fa66c846b34e2ed03f6cb9775b6 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 2 Feb 2022 16:10:14 +0100 Subject: [PATCH 16/38] Enable generator tests for markdown --- test/generators/dune | 3 +- test/generators/gen_rules/gen_rules.ml | 13 + test/generators/link.dune.inc | 4684 ++++++++++++++--- test/generators/markdown/Alias.X.md | 14 + test/generators/markdown/Alias.md | 7 + test/generators/markdown/Bugs.md | 19 + .../Bugs_post_406.class-type-let_open.md | 5 + .../markdown/Bugs_post_406.let_open'.md | 5 + test/generators/markdown/Bugs_post_406.md | 13 + .../markdown/Class.class-type-empty.md | 5 + .../Class.class-type-empty_virtual.md | 5 + .../markdown/Class.class-type-mutually.md | 5 + .../markdown/Class.class-type-polymorphic.md | 5 + .../markdown/Class.class-type-recursive.md | 5 + .../markdown/Class.empty_virtual'.md | 5 + test/generators/markdown/Class.md | 39 + test/generators/markdown/Class.mutually'.md | 5 + .../generators/markdown/Class.polymorphic'.md | 5 + test/generators/markdown/Class.recursive'.md | 5 + test/generators/markdown/External.md | 12 + .../markdown/Functor.F1.argument-1-Arg.md | 11 + test/generators/markdown/Functor.F1.md | 17 + .../markdown/Functor.F2.argument-1-Arg.md | 11 + test/generators/markdown/Functor.F2.md | 19 + .../markdown/Functor.F3.argument-1-Arg.md | 11 + test/generators/markdown/Functor.F3.md | 19 + .../markdown/Functor.F4.argument-1-Arg.md | 11 + test/generators/markdown/Functor.F4.md | 17 + test/generators/markdown/Functor.F5.md | 13 + test/generators/markdown/Functor.md | 31 + .../markdown/Functor.module-type-S.md | 9 + .../Functor.module-type-S1.argument-1-_.md | 11 + .../markdown/Functor.module-type-S1.md | 17 + .../markdown/Functor2.X.argument-1-Y.md | 11 + .../markdown/Functor2.X.argument-2-Z.md | 11 + test/generators/markdown/Functor2.X.md | 37 + test/generators/markdown/Functor2.md | 15 + .../markdown/Functor2.module-type-S.md | 9 + .../Functor2.module-type-XF.argument-1-Y.md | 11 + .../Functor2.module-type-XF.argument-2-Z.md | 11 + .../markdown/Functor2.module-type-XF.md | 37 + test/generators/markdown/Include.md | 47 + .../Include.module-type-Dorminant_Module.md | 11 + .../Include.module-type-Inherent_Module.md | 11 + .../markdown/Include.module-type-Inlined.md | 9 + .../Include.module-type-Not_inlined.md | 9 + ...lude.module-type-Not_inlined_and_closed.md | 9 + ...lude.module-type-Not_inlined_and_opened.md | 9 + test/generators/markdown/Include2.X.md | 13 + test/generators/markdown/Include2.Y.md | 11 + .../markdown/Include2.Y_include_doc.md | 11 + .../markdown/Include2.Y_include_synopsis.md | 13 + test/generators/markdown/Include2.md | 34 + test/generators/markdown/Include_sections.md | 94 + .../Include_sections.module-type-Something.md | 42 + test/generators/markdown/Interlude.md | 54 + test/generators/markdown/Labels.A.md | 7 + test/generators/markdown/Labels.c.md | 7 + .../markdown/Labels.class-type-cs.md | 7 + test/generators/markdown/Labels.md | 140 + .../markdown/Labels.module-type-S.md | 7 + test/generators/markdown/Markup.X.md | 5 + test/generators/markdown/Markup.Y.md | 5 + test/generators/markdown/Markup.md | 183 + test/generators/markdown/Module.M'.md | 5 + test/generators/markdown/Module.Mutually.md | 5 + test/generators/markdown/Module.Recursive.md | 5 + test/generators/markdown/Module.md | 73 + .../markdown/Module.module-type-S.M.md | 7 + .../markdown/Module.module-type-S.md | 25 + .../markdown/Module.module-type-S3.M.md | 7 + .../markdown/Module.module-type-S3.md | 31 + .../markdown/Module.module-type-S4.M.md | 7 + .../markdown/Module.module-type-S4.md | 21 + .../markdown/Module.module-type-S5.M.md | 7 + .../markdown/Module.module-type-S5.md | 21 + .../markdown/Module.module-type-S6.M.md | 7 + .../markdown/Module.module-type-S6.md | 21 + .../markdown/Module.module-type-S7.md | 27 + .../markdown/Module.module-type-S8.md | 21 + .../markdown/Module.module-type-S9.md | 5 + test/generators/markdown/Module_type_alias.md | 34 + .../Module_type_alias.module-type-A.md | 9 + ...e_type_alias.module-type-B.argument-1-C.md | 11 + .../Module_type_alias.module-type-B.md | 17 + ...e_type_alias.module-type-E.argument-1-F.md | 11 + ...e_type_alias.module-type-E.argument-2-C.md | 11 + .../Module_type_alias.module-type-E.md | 21 + ...e_type_alias.module-type-G.argument-1-H.md | 11 + .../Module_type_alias.module-type-G.md | 17 + .../markdown/Module_type_subst.Basic.md | 29 + ...Module_type_subst.Basic.module-type-a.M.md | 9 + .../Module_type_subst.Basic.module-type-a.md | 18 + ...Module_type_subst.Basic.module-type-c.M.md | 9 + .../Module_type_subst.Basic.module-type-c.md | 11 + .../Module_type_subst.Basic.module-type-u.md | 11 + ...subst.Basic.module-type-u.module-type-T.md | 9 + ...odule_type_subst.Basic.module-type-u2.M.md | 9 + .../Module_type_subst.Basic.module-type-u2.md | 15 + ...ubst.Basic.module-type-u2.module-type-T.md | 9 + ...dule_type_subst.Basic.module-type-with_.md | 13 + ...e_type_subst.Basic.module-type-with_2.M.md | 9 + ...ule_type_subst.Basic.module-type-with_2.md | 15 + ....Basic.module-type-with_2.module-type-T.md | 9 + .../markdown/Module_type_subst.Local.md | 27 + ...dule_type_subst.Local.module-type-local.md | 13 + .../Module_type_subst.Local.module-type-s.md | 7 + .../markdown/Module_type_subst.Nested.md | 17 + ..._type_subst.Nested.module-type-nested.N.md | 13 + ...sted.module-type-nested.N.module-type-t.md | 11 + ...le_type_subst.Nested.module-type-nested.md | 11 + ...e_type_subst.Nested.module-type-with_.N.md | 15 + ...ule_type_subst.Nested.module-type-with_.md | 11 + ...e_subst.Nested.module-type-with_subst.N.md | 9 + ...ype_subst.Nested.module-type-with_subst.md | 11 + .../markdown/Module_type_subst.Structural.md | 13 + ...ule_type_subst.Structural.module-type-u.md | 11 + ....Structural.module-type-u.module-type-a.md | 13 + ...dule-type-u.module-type-a.module-type-b.md | 15 + ...dule-type-a.module-type-b.module-type-c.md | 21 + ...ule_type_subst.Structural.module-type-w.md | 11 + ....Structural.module-type-w.module-type-a.md | 13 + ...dule-type-w.module-type-a.module-type-b.md | 15 + ...dule-type-a.module-type-b.module-type-c.md | 21 + test/generators/markdown/Module_type_subst.md | 23 + .../Module_type_subst.module-type-s.md | 5 + .../markdown/Nested.F.argument-1-Arg1.md | 26 + .../markdown/Nested.F.argument-2-Arg2.md | 15 + test/generators/markdown/Nested.F.md | 32 + test/generators/markdown/Nested.X.md | 28 + test/generators/markdown/Nested.inherits.md | 9 + test/generators/markdown/Nested.md | 41 + .../markdown/Nested.module-type-Y.md | 28 + test/generators/markdown/Nested.z.md | 42 + .../generators/markdown/Ocamlary.Aliases.E.md | 17 + .../markdown/Ocamlary.Aliases.Foo.A.md | 19 + .../markdown/Ocamlary.Aliases.Foo.B.md | 19 + .../markdown/Ocamlary.Aliases.Foo.C.md | 19 + .../markdown/Ocamlary.Aliases.Foo.D.md | 19 + .../markdown/Ocamlary.Aliases.Foo.E.md | 19 + .../markdown/Ocamlary.Aliases.Foo.md | 27 + .../markdown/Ocamlary.Aliases.P1.Y.md | 19 + .../markdown/Ocamlary.Aliases.P1.md | 11 + .../markdown/Ocamlary.Aliases.P2.md | 13 + .../markdown/Ocamlary.Aliases.Std.md | 41 + test/generators/markdown/Ocamlary.Aliases.md | 143 + test/generators/markdown/Ocamlary.Buffer.md | 13 + .../Ocamlary.CanonicalTest.Base.List.md | 19 + .../markdown/Ocamlary.CanonicalTest.Base.md | 11 + .../Ocamlary.CanonicalTest.Base_Tests.C.md | 19 + .../Ocamlary.CanonicalTest.Base_Tests.md | 38 + .../Ocamlary.CanonicalTest.List_modif.md | 20 + .../markdown/Ocamlary.CanonicalTest.md | 17 + ...ectionModule.InnerModuleA.InnerModuleA'.md | 20 + .../Ocamlary.CollectionModule.InnerModuleA.md | 30 + ...erModuleA.module-type-InnerModuleTypeA'.md | 20 + .../markdown/Ocamlary.CollectionModule.md | 32 + .../markdown/Ocamlary.Dep1.X.Y.c.md | 17 + test/generators/markdown/Ocamlary.Dep1.X.Y.md | 13 + test/generators/markdown/Ocamlary.Dep1.X.md | 11 + test/generators/markdown/Ocamlary.Dep1.md | 13 + .../markdown/Ocamlary.Dep1.module-type-S.c.md | 15 + .../markdown/Ocamlary.Dep1.module-type-S.md | 11 + test/generators/markdown/Ocamlary.Dep11.md | 9 + .../Ocamlary.Dep11.module-type-S.c.md | 15 + .../markdown/Ocamlary.Dep11.module-type-S.md | 11 + .../markdown/Ocamlary.Dep12.argument-1-Arg.md | 11 + test/generators/markdown/Ocamlary.Dep12.md | 19 + test/generators/markdown/Ocamlary.Dep13.c.md | 13 + test/generators/markdown/Ocamlary.Dep13.md | 9 + test/generators/markdown/Ocamlary.Dep2.A.md | 13 + .../Ocamlary.Dep2.argument-1-Arg.X.md | 15 + .../markdown/Ocamlary.Dep2.argument-1-Arg.md | 15 + test/generators/markdown/Ocamlary.Dep2.md | 23 + test/generators/markdown/Ocamlary.Dep3.md | 9 + test/generators/markdown/Ocamlary.Dep4.X.md | 11 + test/generators/markdown/Ocamlary.Dep4.md | 17 + .../markdown/Ocamlary.Dep4.module-type-S.X.md | 13 + .../markdown/Ocamlary.Dep4.module-type-S.Y.md | 9 + .../markdown/Ocamlary.Dep4.module-type-S.md | 15 + .../markdown/Ocamlary.Dep4.module-type-T.md | 11 + test/generators/markdown/Ocamlary.Dep5.Z.md | 20 + .../markdown/Ocamlary.Dep5.argument-1-Arg.md | 21 + ...ary.Dep5.argument-1-Arg.module-type-S.Y.md | 11 + ...mlary.Dep5.argument-1-Arg.module-type-S.md | 20 + test/generators/markdown/Ocamlary.Dep5.md | 17 + test/generators/markdown/Ocamlary.Dep6.X.Y.md | 13 + test/generators/markdown/Ocamlary.Dep6.X.md | 18 + test/generators/markdown/Ocamlary.Dep6.md | 17 + .../markdown/Ocamlary.Dep6.module-type-S.md | 11 + .../markdown/Ocamlary.Dep6.module-type-T.Y.md | 13 + .../markdown/Ocamlary.Dep6.module-type-T.md | 18 + test/generators/markdown/Ocamlary.Dep7.M.md | 20 + .../Ocamlary.Dep7.argument-1-Arg.X.md | 22 + .../markdown/Ocamlary.Dep7.argument-1-Arg.md | 19 + ...mlary.Dep7.argument-1-Arg.module-type-T.md | 22 + test/generators/markdown/Ocamlary.Dep7.md | 17 + test/generators/markdown/Ocamlary.Dep8.md | 9 + .../markdown/Ocamlary.Dep8.module-type-T.md | 11 + .../markdown/Ocamlary.Dep9.argument-1-X.md | 11 + test/generators/markdown/Ocamlary.Dep9.md | 19 + .../Ocamlary.DoubleInclude1.DoubleInclude2.md | 11 + .../markdown/Ocamlary.DoubleInclude1.md | 9 + .../Ocamlary.DoubleInclude3.DoubleInclude2.md | 11 + .../markdown/Ocamlary.DoubleInclude3.md | 9 + test/generators/markdown/Ocamlary.Empty.md | 9 + test/generators/markdown/Ocamlary.ExtMod.md | 20 + ...1-Collection.InnerModuleA.InnerModuleA'.md | 22 + ...peOf.argument-1-Collection.InnerModuleA.md | 32 + ...erModuleA.module-type-InnerModuleTypeA'.md | 22 + ...ary.FunctorTypeOf.argument-1-Collection.md | 34 + .../markdown/Ocamlary.FunctorTypeOf.md | 24 + ...mlary.IncludeInclude1.IncludeInclude2_M.md | 7 + .../markdown/Ocamlary.IncludeInclude1.md | 13 + ...udeInclude1.module-type-IncludeInclude2.md | 11 + .../markdown/Ocamlary.IncludeInclude2_M.md | 5 + .../generators/markdown/Ocamlary.IncludedA.md | 9 + test/generators/markdown/Ocamlary.M.md | 9 + .../markdown/Ocamlary.ModuleWithSignature.md | 7 + .../Ocamlary.ModuleWithSignatureAlias.md | 9 + test/generators/markdown/Ocamlary.One.md | 9 + .../markdown/Ocamlary.Only_a_module.md | 9 + ...Recollection.InnerModuleA.InnerModuleA'.md | 20 + .../Ocamlary.Recollection.InnerModuleA.md | 30 + ...erModuleA.module-type-InnerModuleTypeA'.md | 20 + ...argument-1-C.InnerModuleA.InnerModuleA'.md | 22 + ....Recollection.argument-1-C.InnerModuleA.md | 32 + ...erModuleA.module-type-InnerModuleTypeA'.md | 22 + .../Ocamlary.Recollection.argument-1-C.md | 34 + .../markdown/Ocamlary.Recollection.md | 46 + test/generators/markdown/Ocamlary.With10.md | 10 + .../Ocamlary.With10.module-type-T.M.md | 13 + .../markdown/Ocamlary.With10.module-type-T.md | 19 + test/generators/markdown/Ocamlary.With2.md | 9 + .../markdown/Ocamlary.With2.module-type-S.md | 11 + test/generators/markdown/Ocamlary.With3.N.md | 11 + test/generators/markdown/Ocamlary.With3.md | 16 + test/generators/markdown/Ocamlary.With4.N.md | 11 + test/generators/markdown/Ocamlary.With4.md | 9 + test/generators/markdown/Ocamlary.With5.N.md | 11 + test/generators/markdown/Ocamlary.With5.md | 13 + .../markdown/Ocamlary.With5.module-type-S.md | 11 + test/generators/markdown/Ocamlary.With6.md | 9 + .../Ocamlary.With6.module-type-T.M.md | 19 + .../markdown/Ocamlary.With6.module-type-T.md | 11 + .../markdown/Ocamlary.With7.argument-1-X.md | 11 + test/generators/markdown/Ocamlary.With7.md | 19 + test/generators/markdown/Ocamlary.With9.md | 9 + .../markdown/Ocamlary.With9.module-type-S.md | 11 + .../markdown/Ocamlary.empty_class.md | 5 + test/generators/markdown/Ocamlary.md | 1362 +++++ ...ule-type-A.Q.InnerModuleA.InnerModuleA'.md | 22 + .../Ocamlary.module-type-A.Q.InnerModuleA.md | 32 + ...erModuleA.module-type-InnerModuleTypeA'.md | 22 + .../markdown/Ocamlary.module-type-A.Q.md | 34 + .../markdown/Ocamlary.module-type-A.md | 13 + ...ule-type-B.Q.InnerModuleA.InnerModuleA'.md | 22 + .../Ocamlary.module-type-B.Q.InnerModuleA.md | 32 + ...erModuleA.module-type-InnerModuleTypeA'.md | 22 + .../markdown/Ocamlary.module-type-B.Q.md | 34 + .../markdown/Ocamlary.module-type-B.md | 13 + ...ule-type-C.Q.InnerModuleA.InnerModuleA'.md | 22 + .../Ocamlary.module-type-C.Q.InnerModuleA.md | 32 + ...erModuleA.module-type-InnerModuleTypeA'.md | 22 + .../markdown/Ocamlary.module-type-C.Q.md | 34 + .../markdown/Ocamlary.module-type-C.md | 20 + ...e-COLLECTION.InnerModuleA.InnerModuleA'.md | 20 + ...ary.module-type-COLLECTION.InnerModuleA.md | 30 + ...erModuleA.module-type-InnerModuleTypeA'.md | 20 + .../Ocamlary.module-type-COLLECTION.md | 34 + .../markdown/Ocamlary.module-type-Dep10.md | 11 + .../markdown/Ocamlary.module-type-Empty.md | 11 + .../markdown/Ocamlary.module-type-EmptySig.md | 7 + .../Ocamlary.module-type-IncludeInclude2.md | 9 + .../Ocamlary.module-type-IncludeModuleType.md | 8 + .../Ocamlary.module-type-IncludedB.md | 9 + .../markdown/Ocamlary.module-type-M.md | 9 + ...e-type-MMM.C.InnerModuleA.InnerModuleA'.md | 22 + ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 32 + ...erModuleA.module-type-InnerModuleTypeA'.md | 22 + .../markdown/Ocamlary.module-type-MMM.C.md | 34 + .../markdown/Ocamlary.module-type-MMM.md | 9 + .../Ocamlary.module-type-MissingComment.md | 11 + .../Ocamlary.module-type-NestedInclude1.md | 9 + ...stedInclude1.module-type-NestedInclude2.md | 11 + .../Ocamlary.module-type-NestedInclude2.md | 9 + .../Ocamlary.module-type-RECOLLECTION.md | 11 + ...ectionModule.InnerModuleA.InnerModuleA'.md | 20 + ...le-type-RecollectionModule.InnerModuleA.md | 30 + ...erModuleA.module-type-InnerModuleTypeA'.md | 20 + ...Ocamlary.module-type-RecollectionModule.md | 34 + .../Ocamlary.module-type-SigForMod.Inner.md | 11 + ...-type-SigForMod.Inner.module-type-Empty.md | 9 + .../Ocamlary.module-type-SigForMod.md | 11 + .../markdown/Ocamlary.module-type-SuperSig.md | 25 + ...dule-type-SuperSig.module-type-EmptySig.md | 11 + ...ry.module-type-SuperSig.module-type-One.md | 11 + ...SuperSig.module-type-SubSigA.SubSigAMod.md | 13 + ...odule-type-SuperSig.module-type-SubSigA.md | 19 + ...odule-type-SuperSig.module-type-SubSigB.md | 15 + ...dule-type-SuperSig.module-type-SuperSig.md | 7 + ...camlary.module-type-ToInclude.IncludedA.md | 11 + .../Ocamlary.module-type-ToInclude.md | 13 + ...le-type-ToInclude.module-type-IncludedB.md | 11 + .../markdown/Ocamlary.module-type-TypeExt.md | 26 + .../Ocamlary.module-type-TypeExtPruned.md | 19 + .../markdown/Ocamlary.module-type-With1.M.md | 11 + .../markdown/Ocamlary.module-type-With1.md | 15 + .../markdown/Ocamlary.module-type-With11.N.md | 13 + .../markdown/Ocamlary.module-type-With11.md | 16 + .../Ocamlary.module-type-With8.M.N.md | 15 + .../markdown/Ocamlary.module-type-With8.M.md | 18 + .../markdown/Ocamlary.module-type-With8.md | 9 + .../markdown/Ocamlary.one_method_class.md | 11 + .../markdown/Ocamlary.param_class.md | 11 + .../markdown/Ocamlary.two_method_class.md | 18 + test/generators/markdown/Recent.X.md | 32 + test/generators/markdown/Recent.Z.Y.X.md | 13 + test/generators/markdown/Recent.Z.Y.md | 11 + test/generators/markdown/Recent.Z.md | 9 + test/generators/markdown/Recent.md | 151 + .../markdown/Recent.module-type-PolyS.md | 19 + .../markdown/Recent.module-type-S.md | 5 + .../Recent.module-type-S1.argument-1-_.md | 7 + .../markdown/Recent.module-type-S1.md | 13 + test/generators/markdown/Recent_impl.B.md | 13 + test/generators/markdown/Recent_impl.Foo.A.md | 15 + test/generators/markdown/Recent_impl.Foo.B.md | 15 + test/generators/markdown/Recent_impl.Foo.md | 13 + test/generators/markdown/Recent_impl.md | 25 + ...ecent_impl.module-type-S.F.argument-1-_.md | 9 + .../markdown/Recent_impl.module-type-S.F.md | 19 + .../markdown/Recent_impl.module-type-S.X.md | 7 + .../markdown/Recent_impl.module-type-S.md | 19 + test/generators/markdown/Section.md | 36 + test/generators/markdown/Stop.N.md | 11 + test/generators/markdown/Stop.md | 30 + .../markdown/Stop_dead_link_doc.Foo.md | 9 + .../generators/markdown/Stop_dead_link_doc.md | 61 + .../markdown/Toplevel_comments.Alias.md | 13 + .../Toplevel_comments.Comments_on_open.M.md | 11 + .../Toplevel_comments.Comments_on_open.md | 15 + .../Toplevel_comments.Include_inline'.md | 13 + .../Toplevel_comments.Include_inline.md | 11 + .../markdown/Toplevel_comments.M''.md | 9 + .../markdown/Toplevel_comments.M'.md | 7 + .../markdown/Toplevel_comments.M.md | 7 + .../Toplevel_comments.Ref_in_synopsis.md | 13 + .../markdown/Toplevel_comments.c1.md | 9 + .../markdown/Toplevel_comments.c2.md | 9 + .../Toplevel_comments.class-type-ct.md | 9 + test/generators/markdown/Toplevel_comments.md | 87 + ..._comments.module-type-Include_inline_T'.md | 13 + ...l_comments.module-type-Include_inline_T.md | 11 + .../Toplevel_comments.module-type-T.md | 13 + test/generators/markdown/Type.md | 452 ++ .../generators/markdown/Type.module-type-X.md | 13 + test/generators/markdown/Val.md | 28 + test/generators/markdown/alias.targets | 2 + test/generators/markdown/bugs.targets | 1 + .../generators/markdown/bugs_post_406.targets | 3 + test/generators/markdown/class.targets | 10 + test/generators/markdown/external.targets | 1 + test/generators/markdown/functor.targets | 13 + test/generators/markdown/functor2.targets | 8 + test/generators/markdown/include.targets | 7 + test/generators/markdown/include2.targets | 5 + .../markdown/include_sections.targets | 2 + test/generators/markdown/interlude.targets | 1 + test/generators/markdown/labels.targets | 5 + test/generators/markdown/markup.targets | 3 + test/generators/markdown/mld.md | 41 + test/generators/markdown/module.targets | 17 + .../markdown/module_type_alias.targets | 9 + .../markdown/module_type_subst.targets | 36 + test/generators/markdown/nested.targets | 8 + test/generators/markdown/ocamlary.targets | 182 + test/generators/markdown/page-mld.targets | 1 + test/generators/markdown/recent.targets | 9 + test/generators/markdown/recent_impl.targets | 9 + test/generators/markdown/section.targets | 1 + test/generators/markdown/stop.targets | 2 + .../markdown/stop_dead_link_doc.targets | 2 + .../markdown/toplevel_comments.targets | 16 + test/generators/markdown/type.targets | 2 + test/generators/markdown/val.targets | 1 + test/integration/markdown.t/intf.mli | 47 - test/integration/markdown.t/markup.mli | 72 - test/integration/markdown.t/run.t | 214 - 389 files changed, 12614 insertions(+), 1012 deletions(-) create mode 100644 test/generators/markdown/Alias.X.md create mode 100644 test/generators/markdown/Alias.md create mode 100644 test/generators/markdown/Bugs.md create mode 100644 test/generators/markdown/Bugs_post_406.class-type-let_open.md create mode 100644 test/generators/markdown/Bugs_post_406.let_open'.md create mode 100644 test/generators/markdown/Bugs_post_406.md create mode 100644 test/generators/markdown/Class.class-type-empty.md create mode 100644 test/generators/markdown/Class.class-type-empty_virtual.md create mode 100644 test/generators/markdown/Class.class-type-mutually.md create mode 100644 test/generators/markdown/Class.class-type-polymorphic.md create mode 100644 test/generators/markdown/Class.class-type-recursive.md create mode 100644 test/generators/markdown/Class.empty_virtual'.md create mode 100644 test/generators/markdown/Class.md create mode 100644 test/generators/markdown/Class.mutually'.md create mode 100644 test/generators/markdown/Class.polymorphic'.md create mode 100644 test/generators/markdown/Class.recursive'.md create mode 100644 test/generators/markdown/External.md create mode 100644 test/generators/markdown/Functor.F1.argument-1-Arg.md create mode 100644 test/generators/markdown/Functor.F1.md create mode 100644 test/generators/markdown/Functor.F2.argument-1-Arg.md create mode 100644 test/generators/markdown/Functor.F2.md create mode 100644 test/generators/markdown/Functor.F3.argument-1-Arg.md create mode 100644 test/generators/markdown/Functor.F3.md create mode 100644 test/generators/markdown/Functor.F4.argument-1-Arg.md create mode 100644 test/generators/markdown/Functor.F4.md create mode 100644 test/generators/markdown/Functor.F5.md create mode 100644 test/generators/markdown/Functor.md create mode 100644 test/generators/markdown/Functor.module-type-S.md create mode 100644 test/generators/markdown/Functor.module-type-S1.argument-1-_.md create mode 100644 test/generators/markdown/Functor.module-type-S1.md create mode 100644 test/generators/markdown/Functor2.X.argument-1-Y.md create mode 100644 test/generators/markdown/Functor2.X.argument-2-Z.md create mode 100644 test/generators/markdown/Functor2.X.md create mode 100644 test/generators/markdown/Functor2.md create mode 100644 test/generators/markdown/Functor2.module-type-S.md create mode 100644 test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md create mode 100644 test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md create mode 100644 test/generators/markdown/Functor2.module-type-XF.md create mode 100644 test/generators/markdown/Include.md create mode 100644 test/generators/markdown/Include.module-type-Dorminant_Module.md create mode 100644 test/generators/markdown/Include.module-type-Inherent_Module.md create mode 100644 test/generators/markdown/Include.module-type-Inlined.md create mode 100644 test/generators/markdown/Include.module-type-Not_inlined.md create mode 100644 test/generators/markdown/Include.module-type-Not_inlined_and_closed.md create mode 100644 test/generators/markdown/Include.module-type-Not_inlined_and_opened.md create mode 100644 test/generators/markdown/Include2.X.md create mode 100644 test/generators/markdown/Include2.Y.md create mode 100644 test/generators/markdown/Include2.Y_include_doc.md create mode 100644 test/generators/markdown/Include2.Y_include_synopsis.md create mode 100644 test/generators/markdown/Include2.md create mode 100644 test/generators/markdown/Include_sections.md create mode 100644 test/generators/markdown/Include_sections.module-type-Something.md create mode 100644 test/generators/markdown/Interlude.md create mode 100644 test/generators/markdown/Labels.A.md create mode 100644 test/generators/markdown/Labels.c.md create mode 100644 test/generators/markdown/Labels.class-type-cs.md create mode 100644 test/generators/markdown/Labels.md create mode 100644 test/generators/markdown/Labels.module-type-S.md create mode 100644 test/generators/markdown/Markup.X.md create mode 100644 test/generators/markdown/Markup.Y.md create mode 100644 test/generators/markdown/Markup.md create mode 100644 test/generators/markdown/Module.M'.md create mode 100644 test/generators/markdown/Module.Mutually.md create mode 100644 test/generators/markdown/Module.Recursive.md create mode 100644 test/generators/markdown/Module.md create mode 100644 test/generators/markdown/Module.module-type-S.M.md create mode 100644 test/generators/markdown/Module.module-type-S.md create mode 100644 test/generators/markdown/Module.module-type-S3.M.md create mode 100644 test/generators/markdown/Module.module-type-S3.md create mode 100644 test/generators/markdown/Module.module-type-S4.M.md create mode 100644 test/generators/markdown/Module.module-type-S4.md create mode 100644 test/generators/markdown/Module.module-type-S5.M.md create mode 100644 test/generators/markdown/Module.module-type-S5.md create mode 100644 test/generators/markdown/Module.module-type-S6.M.md create mode 100644 test/generators/markdown/Module.module-type-S6.md create mode 100644 test/generators/markdown/Module.module-type-S7.md create mode 100644 test/generators/markdown/Module.module-type-S8.md create mode 100644 test/generators/markdown/Module.module-type-S9.md create mode 100644 test/generators/markdown/Module_type_alias.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-A.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-B.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-E.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md create mode 100644 test/generators/markdown/Module_type_alias.module-type-G.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-a.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-c.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-u.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-u2.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-with_.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md create mode 100644 test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md create mode 100644 test/generators/markdown/Module_type_subst.Local.md create mode 100644 test/generators/markdown/Module_type_subst.Local.module-type-local.md create mode 100644 test/generators/markdown/Module_type_subst.Local.module-type-s.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-nested.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-with_.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md create mode 100644 test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-u.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-w.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md create mode 100644 test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md create mode 100644 test/generators/markdown/Module_type_subst.md create mode 100644 test/generators/markdown/Module_type_subst.module-type-s.md create mode 100644 test/generators/markdown/Nested.F.argument-1-Arg1.md create mode 100644 test/generators/markdown/Nested.F.argument-2-Arg2.md create mode 100644 test/generators/markdown/Nested.F.md create mode 100644 test/generators/markdown/Nested.X.md create mode 100644 test/generators/markdown/Nested.inherits.md create mode 100644 test/generators/markdown/Nested.md create mode 100644 test/generators/markdown/Nested.module-type-Y.md create mode 100644 test/generators/markdown/Nested.z.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.E.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Foo.A.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Foo.B.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Foo.C.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Foo.D.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Foo.E.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Foo.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.P1.Y.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.P1.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.P2.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.Std.md create mode 100644 test/generators/markdown/Ocamlary.Aliases.md create mode 100644 test/generators/markdown/Ocamlary.Buffer.md create mode 100644 test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md create mode 100644 test/generators/markdown/Ocamlary.CanonicalTest.Base.md create mode 100644 test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md create mode 100644 test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md create mode 100644 test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md create mode 100644 test/generators/markdown/Ocamlary.CanonicalTest.md create mode 100644 test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.CollectionModule.md create mode 100644 test/generators/markdown/Ocamlary.Dep1.X.Y.c.md create mode 100644 test/generators/markdown/Ocamlary.Dep1.X.Y.md create mode 100644 test/generators/markdown/Ocamlary.Dep1.X.md create mode 100644 test/generators/markdown/Ocamlary.Dep1.md create mode 100644 test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md create mode 100644 test/generators/markdown/Ocamlary.Dep1.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.Dep11.md create mode 100644 test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md create mode 100644 test/generators/markdown/Ocamlary.Dep11.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md create mode 100644 test/generators/markdown/Ocamlary.Dep12.md create mode 100644 test/generators/markdown/Ocamlary.Dep13.c.md create mode 100644 test/generators/markdown/Ocamlary.Dep13.md create mode 100644 test/generators/markdown/Ocamlary.Dep2.A.md create mode 100644 test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md create mode 100644 test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md create mode 100644 test/generators/markdown/Ocamlary.Dep2.md create mode 100644 test/generators/markdown/Ocamlary.Dep3.md create mode 100644 test/generators/markdown/Ocamlary.Dep4.X.md create mode 100644 test/generators/markdown/Ocamlary.Dep4.md create mode 100644 test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md create mode 100644 test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md create mode 100644 test/generators/markdown/Ocamlary.Dep4.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.Dep4.module-type-T.md create mode 100644 test/generators/markdown/Ocamlary.Dep5.Z.md create mode 100644 test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md create mode 100644 test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md create mode 100644 test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.Dep5.md create mode 100644 test/generators/markdown/Ocamlary.Dep6.X.Y.md create mode 100644 test/generators/markdown/Ocamlary.Dep6.X.md create mode 100644 test/generators/markdown/Ocamlary.Dep6.md create mode 100644 test/generators/markdown/Ocamlary.Dep6.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md create mode 100644 test/generators/markdown/Ocamlary.Dep6.module-type-T.md create mode 100644 test/generators/markdown/Ocamlary.Dep7.M.md create mode 100644 test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md create mode 100644 test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md create mode 100644 test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md create mode 100644 test/generators/markdown/Ocamlary.Dep7.md create mode 100644 test/generators/markdown/Ocamlary.Dep8.md create mode 100644 test/generators/markdown/Ocamlary.Dep8.module-type-T.md create mode 100644 test/generators/markdown/Ocamlary.Dep9.argument-1-X.md create mode 100644 test/generators/markdown/Ocamlary.Dep9.md create mode 100644 test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md create mode 100644 test/generators/markdown/Ocamlary.DoubleInclude1.md create mode 100644 test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md create mode 100644 test/generators/markdown/Ocamlary.DoubleInclude3.md create mode 100644 test/generators/markdown/Ocamlary.Empty.md create mode 100644 test/generators/markdown/Ocamlary.ExtMod.md create mode 100644 test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md create mode 100644 test/generators/markdown/Ocamlary.FunctorTypeOf.md create mode 100644 test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md create mode 100644 test/generators/markdown/Ocamlary.IncludeInclude1.md create mode 100644 test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md create mode 100644 test/generators/markdown/Ocamlary.IncludeInclude2_M.md create mode 100644 test/generators/markdown/Ocamlary.IncludedA.md create mode 100644 test/generators/markdown/Ocamlary.M.md create mode 100644 test/generators/markdown/Ocamlary.ModuleWithSignature.md create mode 100644 test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md create mode 100644 test/generators/markdown/Ocamlary.One.md create mode 100644 test/generators/markdown/Ocamlary.Only_a_module.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.argument-1-C.md create mode 100644 test/generators/markdown/Ocamlary.Recollection.md create mode 100644 test/generators/markdown/Ocamlary.With10.md create mode 100644 test/generators/markdown/Ocamlary.With10.module-type-T.M.md create mode 100644 test/generators/markdown/Ocamlary.With10.module-type-T.md create mode 100644 test/generators/markdown/Ocamlary.With2.md create mode 100644 test/generators/markdown/Ocamlary.With2.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.With3.N.md create mode 100644 test/generators/markdown/Ocamlary.With3.md create mode 100644 test/generators/markdown/Ocamlary.With4.N.md create mode 100644 test/generators/markdown/Ocamlary.With4.md create mode 100644 test/generators/markdown/Ocamlary.With5.N.md create mode 100644 test/generators/markdown/Ocamlary.With5.md create mode 100644 test/generators/markdown/Ocamlary.With5.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.With6.md create mode 100644 test/generators/markdown/Ocamlary.With6.module-type-T.M.md create mode 100644 test/generators/markdown/Ocamlary.With6.module-type-T.md create mode 100644 test/generators/markdown/Ocamlary.With7.argument-1-X.md create mode 100644 test/generators/markdown/Ocamlary.With7.md create mode 100644 test/generators/markdown/Ocamlary.With9.md create mode 100644 test/generators/markdown/Ocamlary.With9.module-type-S.md create mode 100644 test/generators/markdown/Ocamlary.empty_class.md create mode 100644 test/generators/markdown/Ocamlary.md create mode 100644 test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-A.Q.md create mode 100644 test/generators/markdown/Ocamlary.module-type-A.md create mode 100644 test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-B.Q.md create mode 100644 test/generators/markdown/Ocamlary.module-type-B.md create mode 100644 test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-C.Q.md create mode 100644 test/generators/markdown/Ocamlary.module-type-C.md create mode 100644 test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-COLLECTION.md create mode 100644 test/generators/markdown/Ocamlary.module-type-Dep10.md create mode 100644 test/generators/markdown/Ocamlary.module-type-Empty.md create mode 100644 test/generators/markdown/Ocamlary.module-type-EmptySig.md create mode 100644 test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md create mode 100644 test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md create mode 100644 test/generators/markdown/Ocamlary.module-type-IncludedB.md create mode 100644 test/generators/markdown/Ocamlary.module-type-M.md create mode 100644 test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-MMM.C.md create mode 100644 test/generators/markdown/Ocamlary.module-type-MMM.md create mode 100644 test/generators/markdown/Ocamlary.module-type-MissingComment.md create mode 100644 test/generators/markdown/Ocamlary.module-type-NestedInclude1.md create mode 100644 test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md create mode 100644 test/generators/markdown/Ocamlary.module-type-NestedInclude2.md create mode 100644 test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md create mode 100644 test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md create mode 100644 test/generators/markdown/Ocamlary.module-type-RecollectionModule.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SigForMod.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md create mode 100644 test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md create mode 100644 test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md create mode 100644 test/generators/markdown/Ocamlary.module-type-ToInclude.md create mode 100644 test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md create mode 100644 test/generators/markdown/Ocamlary.module-type-TypeExt.md create mode 100644 test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With1.M.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With1.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With11.N.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With11.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With8.M.N.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With8.M.md create mode 100644 test/generators/markdown/Ocamlary.module-type-With8.md create mode 100644 test/generators/markdown/Ocamlary.one_method_class.md create mode 100644 test/generators/markdown/Ocamlary.param_class.md create mode 100644 test/generators/markdown/Ocamlary.two_method_class.md create mode 100644 test/generators/markdown/Recent.X.md create mode 100644 test/generators/markdown/Recent.Z.Y.X.md create mode 100644 test/generators/markdown/Recent.Z.Y.md create mode 100644 test/generators/markdown/Recent.Z.md create mode 100644 test/generators/markdown/Recent.md create mode 100644 test/generators/markdown/Recent.module-type-PolyS.md create mode 100644 test/generators/markdown/Recent.module-type-S.md create mode 100644 test/generators/markdown/Recent.module-type-S1.argument-1-_.md create mode 100644 test/generators/markdown/Recent.module-type-S1.md create mode 100644 test/generators/markdown/Recent_impl.B.md create mode 100644 test/generators/markdown/Recent_impl.Foo.A.md create mode 100644 test/generators/markdown/Recent_impl.Foo.B.md create mode 100644 test/generators/markdown/Recent_impl.Foo.md create mode 100644 test/generators/markdown/Recent_impl.md create mode 100644 test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md create mode 100644 test/generators/markdown/Recent_impl.module-type-S.F.md create mode 100644 test/generators/markdown/Recent_impl.module-type-S.X.md create mode 100644 test/generators/markdown/Recent_impl.module-type-S.md create mode 100644 test/generators/markdown/Section.md create mode 100644 test/generators/markdown/Stop.N.md create mode 100644 test/generators/markdown/Stop.md create mode 100644 test/generators/markdown/Stop_dead_link_doc.Foo.md create mode 100644 test/generators/markdown/Stop_dead_link_doc.md create mode 100644 test/generators/markdown/Toplevel_comments.Alias.md create mode 100644 test/generators/markdown/Toplevel_comments.Comments_on_open.M.md create mode 100644 test/generators/markdown/Toplevel_comments.Comments_on_open.md create mode 100644 test/generators/markdown/Toplevel_comments.Include_inline'.md create mode 100644 test/generators/markdown/Toplevel_comments.Include_inline.md create mode 100644 test/generators/markdown/Toplevel_comments.M''.md create mode 100644 test/generators/markdown/Toplevel_comments.M'.md create mode 100644 test/generators/markdown/Toplevel_comments.M.md create mode 100644 test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md create mode 100644 test/generators/markdown/Toplevel_comments.c1.md create mode 100644 test/generators/markdown/Toplevel_comments.c2.md create mode 100644 test/generators/markdown/Toplevel_comments.class-type-ct.md create mode 100644 test/generators/markdown/Toplevel_comments.md create mode 100644 test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md create mode 100644 test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md create mode 100644 test/generators/markdown/Toplevel_comments.module-type-T.md create mode 100644 test/generators/markdown/Type.md create mode 100644 test/generators/markdown/Type.module-type-X.md create mode 100644 test/generators/markdown/Val.md create mode 100644 test/generators/markdown/alias.targets create mode 100644 test/generators/markdown/bugs.targets create mode 100644 test/generators/markdown/bugs_post_406.targets create mode 100644 test/generators/markdown/class.targets create mode 100644 test/generators/markdown/external.targets create mode 100644 test/generators/markdown/functor.targets create mode 100644 test/generators/markdown/functor2.targets create mode 100644 test/generators/markdown/include.targets create mode 100644 test/generators/markdown/include2.targets create mode 100644 test/generators/markdown/include_sections.targets create mode 100644 test/generators/markdown/interlude.targets create mode 100644 test/generators/markdown/labels.targets create mode 100644 test/generators/markdown/markup.targets create mode 100644 test/generators/markdown/mld.md create mode 100644 test/generators/markdown/module.targets create mode 100644 test/generators/markdown/module_type_alias.targets create mode 100644 test/generators/markdown/module_type_subst.targets create mode 100644 test/generators/markdown/nested.targets create mode 100644 test/generators/markdown/ocamlary.targets create mode 100644 test/generators/markdown/page-mld.targets create mode 100644 test/generators/markdown/recent.targets create mode 100644 test/generators/markdown/recent_impl.targets create mode 100644 test/generators/markdown/section.targets create mode 100644 test/generators/markdown/stop.targets create mode 100644 test/generators/markdown/stop_dead_link_doc.targets create mode 100644 test/generators/markdown/toplevel_comments.targets create mode 100644 test/generators/markdown/type.targets create mode 100644 test/generators/markdown/val.targets delete mode 100644 test/integration/markdown.t/intf.mli delete mode 100644 test/integration/markdown.t/markup.mli delete mode 100644 test/integration/markdown.t/run.t diff --git a/test/generators/dune b/test/generators/dune index ba813043e2..3391793980 100644 --- a/test/generators/dune +++ b/test/generators/dune @@ -5,7 +5,8 @@ (glob_files cases/*) (glob_files html/*.targets) (glob_files latex/*.targets) - (glob_files man/*.targets)) + (glob_files man/*.targets) + (glob_files markdown/*.targets)) (enabled_if (>= %{ocaml_version} 4.04)) (action diff --git a/test/generators/gen_rules/gen_rules.ml b/test/generators/gen_rules/gen_rules.ml index 617e01fa01..107354af9a 100644 --- a/test/generators/gen_rules/gen_rules.ml +++ b/test/generators/gen_rules/gen_rules.ml @@ -37,6 +37,18 @@ let man_target_rule path = Gen_rules_lib.Dune.arg_dep path; ] +let markdown_target_rule path = + [ + "odoc"; + "markdown-generate"; + "--generate-links"; + "-o"; + "."; + "--extra-suffix"; + "gen"; + Gen_rules_lib.Dune.arg_dep path; + ] + (** Returns filenames, not paths. *) let read_files_from_dir dir = let arr = Sys.readdir (Fpath.to_string dir) in @@ -100,6 +112,7 @@ let () = (html_target_rule, Fpath.v "html", Some "--flat"); (latex_target_rule, Fpath.v "latex", None); (man_target_rule, Fpath.v "man", None); + (markdown_target_rule, Fpath.v "markdown", None); ] cases in diff --git a/test/generators/link.dune.inc b/test/generators/link.dune.inc index 0a80c76332..e8f32b99af 100644 --- a/test/generators/link.dune.inc +++ b/test/generators/link.dune.inc @@ -551,6 +551,41 @@ (action (diff alias.targets alias.targets.gen)))) +(subdir + markdown + (rule + (targets Alias.md.gen Alias.X.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../alias.odocl}))) + (rule + (alias runtest) + (action + (diff Alias.md Alias.md.gen))) + (rule + (alias runtest) + (action + (diff Alias.X.md Alias.X.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + alias.targets.gen + (run odoc markdown-targets -o . %{dep:../alias.odocl})))) + (rule + (alias runtest) + (action + (diff alias.targets alias.targets.gen)))) + (subdir html (rule @@ -629,6 +664,37 @@ (action (diff bugs.targets bugs.targets.gen)))) +(subdir + markdown + (rule + (targets Bugs.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../bugs.odocl}))) + (rule + (alias runtest) + (action + (diff Bugs.md Bugs.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + bugs.targets.gen + (run odoc markdown-targets -o . %{dep:../bugs.odocl})))) + (rule + (alias runtest) + (action + (diff bugs.targets bugs.targets.gen)))) + (subdir html (rule @@ -776,6 +842,62 @@ (enabled_if (>= %{ocaml_version} 4.06)))) +(subdir + markdown + (rule + (targets + Bugs_post_406.md.gen + Bugs_post_406.class-type-let_open.md.gen + Bugs_post_406.let_open'.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../bugs_post_406.odocl})) + (enabled_if + (>= %{ocaml_version} 4.06))) + (rule + (alias runtest) + (action + (diff Bugs_post_406.md Bugs_post_406.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.06))) + (rule + (alias runtest) + (action + (diff + Bugs_post_406.class-type-let_open.md + Bugs_post_406.class-type-let_open.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.06))) + (rule + (alias runtest) + (action + (diff Bugs_post_406.let_open'.md Bugs_post_406.let_open'.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.06)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + bugs_post_406.targets.gen + (run odoc markdown-targets -o . %{dep:../bugs_post_406.odocl}))) + (enabled_if + (>= %{ocaml_version} 4.06))) + (rule + (alias runtest) + (action + (diff bugs_post_406.targets bugs_post_406.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.06)))) + (subdir html (rule @@ -892,6 +1014,22 @@ (enabled_if (<= %{ocaml_version} 4.09)))) +(subdir + markdown + (rule + (action + (with-outputs-to + bugs_pre_410.targets.gen + (run odoc markdown-targets -o . %{dep:../bugs_pre_410.odocl}))) + (enabled_if + (<= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff bugs_pre_410.targets bugs_pre_410.targets.gen)) + (enabled_if + (<= %{ocaml_version} 4.09)))) + (subdir html (rule @@ -1062,6 +1200,85 @@ (action (diff class.targets class.targets.gen)))) +(subdir + markdown + (rule + (targets + Class.md.gen + Class.class-type-empty.md.gen + Class.class-type-mutually.md.gen + Class.class-type-recursive.md.gen + Class.mutually'.md.gen + Class.recursive'.md.gen + Class.class-type-empty_virtual.md.gen + Class.empty_virtual'.md.gen + Class.class-type-polymorphic.md.gen + Class.polymorphic'.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../class.odocl}))) + (rule + (alias runtest) + (action + (diff Class.md Class.md.gen))) + (rule + (alias runtest) + (action + (diff Class.class-type-empty.md Class.class-type-empty.md.gen))) + (rule + (alias runtest) + (action + (diff Class.class-type-mutually.md Class.class-type-mutually.md.gen))) + (rule + (alias runtest) + (action + (diff Class.class-type-recursive.md Class.class-type-recursive.md.gen))) + (rule + (alias runtest) + (action + (diff Class.mutually'.md Class.mutually'.md.gen))) + (rule + (alias runtest) + (action + (diff Class.recursive'.md Class.recursive'.md.gen))) + (rule + (alias runtest) + (action + (diff + Class.class-type-empty_virtual.md + Class.class-type-empty_virtual.md.gen))) + (rule + (alias runtest) + (action + (diff Class.empty_virtual'.md Class.empty_virtual'.md.gen))) + (rule + (alias runtest) + (action + (diff Class.class-type-polymorphic.md Class.class-type-polymorphic.md.gen))) + (rule + (alias runtest) + (action + (diff Class.polymorphic'.md Class.polymorphic'.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + class.targets.gen + (run odoc markdown-targets -o . %{dep:../class.odocl})))) + (rule + (alias runtest) + (action + (diff class.targets class.targets.gen)))) + (subdir html (rule @@ -1140,6 +1357,37 @@ (action (diff external.targets external.targets.gen)))) +(subdir + markdown + (rule + (targets External.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../external.odocl}))) + (rule + (alias runtest) + (action + (diff External.md External.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + external.targets.gen + (run odoc markdown-targets -o . %{dep:../external.odocl})))) + (rule + (alias runtest) + (action + (diff external.targets external.targets.gen)))) + (subdir html (rule @@ -1333,6 +1581,100 @@ (action (diff functor.targets functor.targets.gen)))) +(subdir + markdown + (rule + (targets + Functor.md.gen + Functor.module-type-S.md.gen + Functor.module-type-S1.md.gen + Functor.module-type-S1.argument-1-_.md.gen + Functor.F1.md.gen + Functor.F1.argument-1-Arg.md.gen + Functor.F2.md.gen + Functor.F2.argument-1-Arg.md.gen + Functor.F3.md.gen + Functor.F3.argument-1-Arg.md.gen + Functor.F4.md.gen + Functor.F4.argument-1-Arg.md.gen + Functor.F5.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../functor.odocl}))) + (rule + (alias runtest) + (action + (diff Functor.md Functor.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.module-type-S.md Functor.module-type-S.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.module-type-S1.md Functor.module-type-S1.md.gen))) + (rule + (alias runtest) + (action + (diff + Functor.module-type-S1.argument-1-_.md + Functor.module-type-S1.argument-1-_.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F1.md Functor.F1.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F1.argument-1-Arg.md Functor.F1.argument-1-Arg.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F2.md Functor.F2.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F2.argument-1-Arg.md Functor.F2.argument-1-Arg.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F3.md Functor.F3.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F3.argument-1-Arg.md Functor.F3.argument-1-Arg.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F4.md Functor.F4.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F4.argument-1-Arg.md Functor.F4.argument-1-Arg.md.gen))) + (rule + (alias runtest) + (action + (diff Functor.F5.md Functor.F5.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + functor.targets.gen + (run odoc markdown-targets -o . %{dep:../functor.odocl})))) + (rule + (alias runtest) + (action + (diff functor.targets functor.targets.gen)))) + (subdir html (rule @@ -1460,16 +1802,87 @@ (diff functor2.targets functor2.targets.gen)))) (subdir - html + markdown (rule (targets - Include.html.gen - Include-module-type-Not_inlined.html.gen - Include-module-type-Inlined.html.gen - Include-module-type-Not_inlined_and_closed.html.gen - Include-module-type-Not_inlined_and_opened.html.gen - Include-module-type-Inherent_Module.html.gen - Include-module-type-Dorminant_Module.html.gen) + Functor2.md.gen + Functor2.module-type-S.md.gen + Functor2.X.md.gen + Functor2.X.argument-1-Y.md.gen + Functor2.X.argument-2-Z.md.gen + Functor2.module-type-XF.md.gen + Functor2.module-type-XF.argument-1-Y.md.gen + Functor2.module-type-XF.argument-2-Z.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../functor2.odocl}))) + (rule + (alias runtest) + (action + (diff Functor2.md Functor2.md.gen))) + (rule + (alias runtest) + (action + (diff Functor2.module-type-S.md Functor2.module-type-S.md.gen))) + (rule + (alias runtest) + (action + (diff Functor2.X.md Functor2.X.md.gen))) + (rule + (alias runtest) + (action + (diff Functor2.X.argument-1-Y.md Functor2.X.argument-1-Y.md.gen))) + (rule + (alias runtest) + (action + (diff Functor2.X.argument-2-Z.md Functor2.X.argument-2-Z.md.gen))) + (rule + (alias runtest) + (action + (diff Functor2.module-type-XF.md Functor2.module-type-XF.md.gen))) + (rule + (alias runtest) + (action + (diff + Functor2.module-type-XF.argument-1-Y.md + Functor2.module-type-XF.argument-1-Y.md.gen))) + (rule + (alias runtest) + (action + (diff + Functor2.module-type-XF.argument-2-Z.md + Functor2.module-type-XF.argument-2-Z.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + functor2.targets.gen + (run odoc markdown-targets -o . %{dep:../functor2.odocl})))) + (rule + (alias runtest) + (action + (diff functor2.targets functor2.targets.gen)))) + +(subdir + html + (rule + (targets + Include.html.gen + Include-module-type-Not_inlined.html.gen + Include-module-type-Inlined.html.gen + Include-module-type-Not_inlined_and_closed.html.gen + Include-module-type-Not_inlined_and_opened.html.gen + Include-module-type-Inherent_Module.html.gen + Include-module-type-Dorminant_Module.html.gen) (action (run odoc @@ -1580,6 +1993,78 @@ (action (diff include.targets include.targets.gen)))) +(subdir + markdown + (rule + (targets + Include.md.gen + Include.module-type-Not_inlined.md.gen + Include.module-type-Inlined.md.gen + Include.module-type-Not_inlined_and_closed.md.gen + Include.module-type-Not_inlined_and_opened.md.gen + Include.module-type-Inherent_Module.md.gen + Include.module-type-Dorminant_Module.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../include.odocl}))) + (rule + (alias runtest) + (action + (diff Include.md Include.md.gen))) + (rule + (alias runtest) + (action + (diff + Include.module-type-Not_inlined.md + Include.module-type-Not_inlined.md.gen))) + (rule + (alias runtest) + (action + (diff Include.module-type-Inlined.md Include.module-type-Inlined.md.gen))) + (rule + (alias runtest) + (action + (diff + Include.module-type-Not_inlined_and_closed.md + Include.module-type-Not_inlined_and_closed.md.gen))) + (rule + (alias runtest) + (action + (diff + Include.module-type-Not_inlined_and_opened.md + Include.module-type-Not_inlined_and_opened.md.gen))) + (rule + (alias runtest) + (action + (diff + Include.module-type-Inherent_Module.md + Include.module-type-Inherent_Module.md.gen))) + (rule + (alias runtest) + (action + (diff + Include.module-type-Dorminant_Module.md + Include.module-type-Dorminant_Module.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + include.targets.gen + (run odoc markdown-targets -o . %{dep:../include.odocl})))) + (rule + (alias runtest) + (action + (diff include.targets include.targets.gen)))) + (subdir html (rule @@ -1702,6 +2187,58 @@ (action (diff include2.targets include2.targets.gen)))) +(subdir + markdown + (rule + (targets + Include2.md.gen + Include2.X.md.gen + Include2.Y.md.gen + Include2.Y_include_synopsis.md.gen + Include2.Y_include_doc.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../include2.odocl}))) + (rule + (alias runtest) + (action + (diff Include2.md Include2.md.gen))) + (rule + (alias runtest) + (action + (diff Include2.X.md Include2.X.md.gen))) + (rule + (alias runtest) + (action + (diff Include2.Y.md Include2.Y.md.gen))) + (rule + (alias runtest) + (action + (diff Include2.Y_include_synopsis.md Include2.Y_include_synopsis.md.gen))) + (rule + (alias runtest) + (action + (diff Include2.Y_include_doc.md Include2.Y_include_doc.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + include2.targets.gen + (run odoc markdown-targets -o . %{dep:../include2.odocl})))) + (rule + (alias runtest) + (action + (diff include2.targets include2.targets.gen)))) + (subdir html (rule @@ -1802,6 +2339,45 @@ (action (diff include_sections.targets include_sections.targets.gen)))) +(subdir + markdown + (rule + (targets + Include_sections.md.gen + Include_sections.module-type-Something.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../include_sections.odocl}))) + (rule + (alias runtest) + (action + (diff Include_sections.md Include_sections.md.gen))) + (rule + (alias runtest) + (action + (diff + Include_sections.module-type-Something.md + Include_sections.module-type-Something.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + include_sections.targets.gen + (run odoc markdown-targets -o . %{dep:../include_sections.odocl})))) + (rule + (alias runtest) + (action + (diff include_sections.targets include_sections.targets.gen)))) + (subdir html (rule @@ -1887,6 +2463,37 @@ (action (diff interlude.targets interlude.targets.gen)))) +(subdir + markdown + (rule + (targets Interlude.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../interlude.odocl}))) + (rule + (alias runtest) + (action + (diff Interlude.md Interlude.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + interlude.targets.gen + (run odoc markdown-targets -o . %{dep:../interlude.odocl})))) + (rule + (alias runtest) + (action + (diff interlude.targets interlude.targets.gen)))) + (subdir html (rule @@ -2036,6 +2643,74 @@ (enabled_if (>= %{ocaml_version} 4.09)))) +(subdir + markdown + (rule + (targets + Labels.md.gen + Labels.A.md.gen + Labels.module-type-S.md.gen + Labels.c.md.gen + Labels.class-type-cs.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../labels.odocl})) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Labels.md Labels.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Labels.A.md Labels.A.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Labels.module-type-S.md Labels.module-type-S.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Labels.c.md Labels.c.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Labels.class-type-cs.md Labels.class-type-cs.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + labels.targets.gen + (run odoc markdown-targets -o . %{dep:../labels.odocl}))) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff labels.targets labels.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.09)))) + (subdir html (rule @@ -2131,21 +2806,60 @@ (diff markup.targets markup.targets.gen)))) (subdir - html + markdown (rule - (targets mld.html.gen) + (targets Markup.md.gen Markup.X.md.gen Markup.Y.md.gen) (action (run odoc - html-generate - --indent - --flat - --extra-suffix - gen + markdown-generate + --generate-links -o . - %{dep:../page-mld.odocl}))) - (rule + --extra-suffix + gen + %{dep:../markup.odocl}))) + (rule + (alias runtest) + (action + (diff Markup.md Markup.md.gen))) + (rule + (alias runtest) + (action + (diff Markup.X.md Markup.X.md.gen))) + (rule + (alias runtest) + (action + (diff Markup.Y.md Markup.Y.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + markup.targets.gen + (run odoc markdown-targets -o . %{dep:../markup.odocl})))) + (rule + (alias runtest) + (action + (diff markup.targets markup.targets.gen)))) + +(subdir + html + (rule + (targets mld.html.gen) + (action + (run + odoc + html-generate + --indent + --flat + --extra-suffix + gen + -o + . + %{dep:../page-mld.odocl}))) + (rule (alias runtest) (action (diff mld.html mld.html.gen)))) @@ -2208,6 +2922,37 @@ (action (diff page-mld.targets page-mld.targets.gen)))) +(subdir + markdown + (rule + (targets mld.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../page-mld.odocl}))) + (rule + (alias runtest) + (action + (diff mld.md mld.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + page-mld.targets.gen + (run odoc markdown-targets -o . %{dep:../page-mld.odocl})))) + (rule + (alias runtest) + (action + (diff page-mld.targets page-mld.targets.gen)))) + (subdir html (rule @@ -2383,6 +3128,118 @@ (action (diff module.targets module.targets.gen)))) +(subdir + markdown + (rule + (targets + Module.md.gen + Module.module-type-S.md.gen + Module.module-type-S.M.md.gen + Module.module-type-S3.md.gen + Module.module-type-S3.M.md.gen + Module.module-type-S4.md.gen + Module.module-type-S4.M.md.gen + Module.module-type-S5.md.gen + Module.module-type-S5.M.md.gen + Module.module-type-S6.md.gen + Module.module-type-S6.M.md.gen + Module.M'.md.gen + Module.module-type-S7.md.gen + Module.module-type-S8.md.gen + Module.module-type-S9.md.gen + Module.Mutually.md.gen + Module.Recursive.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../module.odocl}))) + (rule + (alias runtest) + (action + (diff Module.md Module.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S.md Module.module-type-S.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S.M.md Module.module-type-S.M.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S3.md Module.module-type-S3.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S3.M.md Module.module-type-S3.M.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S4.md Module.module-type-S4.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S4.M.md Module.module-type-S4.M.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S5.md Module.module-type-S5.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S5.M.md Module.module-type-S5.M.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S6.md Module.module-type-S6.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S6.M.md Module.module-type-S6.M.md.gen))) + (rule + (alias runtest) + (action + (diff Module.M'.md Module.M'.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S7.md Module.module-type-S7.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S8.md Module.module-type-S8.md.gen))) + (rule + (alias runtest) + (action + (diff Module.module-type-S9.md Module.module-type-S9.md.gen))) + (rule + (alias runtest) + (action + (diff Module.Mutually.md Module.Mutually.md.gen))) + (rule + (alias runtest) + (action + (diff Module.Recursive.md Module.Recursive.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + module.targets.gen + (run odoc markdown-targets -o . %{dep:../module.odocl})))) + (rule + (alias runtest) + (action + (diff module.targets module.targets.gen)))) + (subdir html (rule @@ -2532,6 +3389,94 @@ (action (diff module_type_alias.targets module_type_alias.targets.gen)))) +(subdir + markdown + (rule + (targets + Module_type_alias.md.gen + Module_type_alias.module-type-A.md.gen + Module_type_alias.module-type-B.md.gen + Module_type_alias.module-type-B.argument-1-C.md.gen + Module_type_alias.module-type-E.md.gen + Module_type_alias.module-type-E.argument-1-F.md.gen + Module_type_alias.module-type-E.argument-2-C.md.gen + Module_type_alias.module-type-G.md.gen + Module_type_alias.module-type-G.argument-1-H.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../module_type_alias.odocl}))) + (rule + (alias runtest) + (action + (diff Module_type_alias.md Module_type_alias.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-A.md + Module_type_alias.module-type-A.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-B.md + Module_type_alias.module-type-B.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-B.argument-1-C.md + Module_type_alias.module-type-B.argument-1-C.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-E.md + Module_type_alias.module-type-E.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-E.argument-1-F.md + Module_type_alias.module-type-E.argument-1-F.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-E.argument-2-C.md + Module_type_alias.module-type-E.argument-2-C.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-G.md + Module_type_alias.module-type-G.md.gen))) + (rule + (alias runtest) + (action + (diff + Module_type_alias.module-type-G.argument-1-H.md + Module_type_alias.module-type-G.argument-1-H.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + module_type_alias.targets.gen + (run odoc markdown-targets -o . %{dep:../module_type_alias.odocl})))) + (rule + (alias runtest) + (action + (diff module_type_alias.targets module_type_alias.targets.gen)))) + (subdir html (rule @@ -2988,75 +3933,422 @@ (>= %{ocaml_version} 4.13)))) (subdir - html + markdown (rule (targets - Nested.html.gen - Nested-X.html.gen - Nested-module-type-Y.html.gen - Nested-F.html.gen - Nested-F-argument-1-Arg1.html.gen - Nested-F-argument-2-Arg2.html.gen - Nested-class-z.html.gen - Nested-class-inherits.html.gen) + Module_type_subst.md.gen + Module_type_subst.Local.md.gen + Module_type_subst.Local.module-type-local.md.gen + Module_type_subst.Local.module-type-s.md.gen + Module_type_subst.module-type-s.md.gen + Module_type_subst.Basic.md.gen + Module_type_subst.Basic.module-type-u.md.gen + Module_type_subst.Basic.module-type-u.module-type-T.md.gen + Module_type_subst.Basic.module-type-with_.md.gen + Module_type_subst.Basic.module-type-u2.md.gen + Module_type_subst.Basic.module-type-u2.module-type-T.md.gen + Module_type_subst.Basic.module-type-u2.M.md.gen + Module_type_subst.Basic.module-type-with_2.md.gen + Module_type_subst.Basic.module-type-with_2.module-type-T.md.gen + Module_type_subst.Basic.module-type-with_2.M.md.gen + Module_type_subst.Basic.module-type-a.md.gen + Module_type_subst.Basic.module-type-a.M.md.gen + Module_type_subst.Basic.module-type-c.md.gen + Module_type_subst.Basic.module-type-c.M.md.gen + Module_type_subst.Nested.md.gen + Module_type_subst.Nested.module-type-nested.md.gen + Module_type_subst.Nested.module-type-nested.N.md.gen + Module_type_subst.Nested.module-type-nested.N.module-type-t.md.gen + Module_type_subst.Nested.module-type-with_.md.gen + Module_type_subst.Nested.module-type-with_.N.md.gen + Module_type_subst.Nested.module-type-with_subst.md.gen + Module_type_subst.Nested.module-type-with_subst.N.md.gen + Module_type_subst.Structural.md.gen + Module_type_subst.Structural.module-type-u.md.gen + Module_type_subst.Structural.module-type-u.module-type-a.md.gen + Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md.gen + Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md.gen + Module_type_subst.Structural.module-type-w.md.gen + Module_type_subst.Structural.module-type-w.module-type-a.md.gen + Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md.gen + Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md.gen) (action (run odoc - html-generate - --indent - --flat - --extra-suffix - gen + markdown-generate + --generate-links -o . - %{dep:../nested.odocl}))) + --extra-suffix + gen + %{dep:../module_type_subst.odocl})) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested.html Nested.html.gen))) + (diff Module_type_subst.md Module_type_subst.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-X.html Nested-X.html.gen))) + (diff Module_type_subst.Local.md Module_type_subst.Local.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-module-type-Y.html Nested-module-type-Y.html.gen))) + (diff + Module_type_subst.Local.module-type-local.md + Module_type_subst.Local.module-type-local.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-F.html Nested-F.html.gen))) + (diff + Module_type_subst.Local.module-type-s.md + Module_type_subst.Local.module-type-s.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-F-argument-1-Arg1.html Nested-F-argument-1-Arg1.html.gen))) + (diff + Module_type_subst.module-type-s.md + Module_type_subst.module-type-s.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-F-argument-2-Arg2.html Nested-F-argument-2-Arg2.html.gen))) + (diff Module_type_subst.Basic.md Module_type_subst.Basic.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-class-z.html Nested-class-z.html.gen))) + (diff + Module_type_subst.Basic.module-type-u.md + Module_type_subst.Basic.module-type-u.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff Nested-class-inherits.html Nested-class-inherits.html.gen)))) - -(subdir - html + (diff + Module_type_subst.Basic.module-type-u.module-type-T.md + Module_type_subst.Basic.module-type-u.module-type-T.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule + (alias runtest) (action - (with-outputs-to - nested.targets.gen - (run odoc html-targets -o . %{dep:../nested.odocl} --flat)))) + (diff + Module_type_subst.Basic.module-type-with_.md + Module_type_subst.Basic.module-type-with_.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) (rule (alias runtest) (action - (diff nested.targets nested.targets.gen)))) - -(subdir - latex + (diff + Module_type_subst.Basic.module-type-u2.md + Module_type_subst.Basic.module-type-u2.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-u2.module-type-T.md + Module_type_subst.Basic.module-type-u2.module-type-T.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-u2.M.md + Module_type_subst.Basic.module-type-u2.M.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-with_2.md + Module_type_subst.Basic.module-type-with_2.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-with_2.module-type-T.md + Module_type_subst.Basic.module-type-with_2.module-type-T.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-with_2.M.md + Module_type_subst.Basic.module-type-with_2.M.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-a.md + Module_type_subst.Basic.module-type-a.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-a.M.md + Module_type_subst.Basic.module-type-a.M.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-c.md + Module_type_subst.Basic.module-type-c.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Basic.module-type-c.M.md + Module_type_subst.Basic.module-type-c.M.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff Module_type_subst.Nested.md Module_type_subst.Nested.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-nested.md + Module_type_subst.Nested.module-type-nested.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-nested.N.md + Module_type_subst.Nested.module-type-nested.N.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-nested.N.module-type-t.md + Module_type_subst.Nested.module-type-nested.N.module-type-t.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-with_.md + Module_type_subst.Nested.module-type-with_.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-with_.N.md + Module_type_subst.Nested.module-type-with_.N.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-with_subst.md + Module_type_subst.Nested.module-type-with_subst.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Nested.module-type-with_subst.N.md + Module_type_subst.Nested.module-type-with_subst.N.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff Module_type_subst.Structural.md Module_type_subst.Structural.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-u.md + Module_type_subst.Structural.module-type-u.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-u.module-type-a.md + Module_type_subst.Structural.module-type-u.module-type-a.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md + Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md + Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-w.md + Module_type_subst.Structural.module-type-w.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-w.module-type-a.md + Module_type_subst.Structural.module-type-w.module-type-a.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md + Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff + Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md + Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.13)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + module_type_subst.targets.gen + (run odoc markdown-targets -o . %{dep:../module_type_subst.odocl}))) + (enabled_if + (>= %{ocaml_version} 4.13))) + (rule + (alias runtest) + (action + (diff module_type_subst.targets module_type_subst.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.13)))) + +(subdir + html + (rule + (targets + Nested.html.gen + Nested-X.html.gen + Nested-module-type-Y.html.gen + Nested-F.html.gen + Nested-F-argument-1-Arg1.html.gen + Nested-F-argument-2-Arg2.html.gen + Nested-class-z.html.gen + Nested-class-inherits.html.gen) + (action + (run + odoc + html-generate + --indent + --flat + --extra-suffix + gen + -o + . + %{dep:../nested.odocl}))) + (rule + (alias runtest) + (action + (diff Nested.html Nested.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-X.html Nested-X.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-module-type-Y.html Nested-module-type-Y.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-F.html Nested-F.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-F-argument-1-Arg1.html Nested-F-argument-1-Arg1.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-F-argument-2-Arg2.html Nested-F-argument-2-Arg2.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-class-z.html Nested-class-z.html.gen))) + (rule + (alias runtest) + (action + (diff Nested-class-inherits.html Nested-class-inherits.html.gen)))) + +(subdir + html + (rule + (action + (with-outputs-to + nested.targets.gen + (run odoc html-targets -o . %{dep:../nested.odocl} --flat)))) + (rule + (alias runtest) + (action + (diff nested.targets nested.targets.gen)))) + +(subdir + latex (rule (targets Nested.tex.gen @@ -3139,22 +4431,89 @@ (diff nested.targets nested.targets.gen)))) (subdir - html + markdown (rule (targets - Ocamlary.html.gen - Ocamlary-Empty.html.gen - Ocamlary-module-type-Empty.html.gen - Ocamlary-module-type-MissingComment.html.gen - Ocamlary-module-type-EmptySig.html.gen - Ocamlary-ModuleWithSignature.html.gen - Ocamlary-ModuleWithSignatureAlias.html.gen - Ocamlary-One.html.gen - Ocamlary-module-type-SigForMod.html.gen - Ocamlary-module-type-SigForMod-Inner.html.gen - Ocamlary-module-type-SigForMod-Inner-module-type-Empty.html.gen - Ocamlary-module-type-SuperSig.html.gen - Ocamlary-module-type-SuperSig-module-type-SubSigA.html.gen + Nested.md.gen + Nested.X.md.gen + Nested.module-type-Y.md.gen + Nested.F.md.gen + Nested.F.argument-1-Arg1.md.gen + Nested.F.argument-2-Arg2.md.gen + Nested.z.md.gen + Nested.inherits.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../nested.odocl}))) + (rule + (alias runtest) + (action + (diff Nested.md Nested.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.X.md Nested.X.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.module-type-Y.md Nested.module-type-Y.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.F.md Nested.F.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.F.argument-1-Arg1.md Nested.F.argument-1-Arg1.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.F.argument-2-Arg2.md Nested.F.argument-2-Arg2.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.z.md Nested.z.md.gen))) + (rule + (alias runtest) + (action + (diff Nested.inherits.md Nested.inherits.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + nested.targets.gen + (run odoc markdown-targets -o . %{dep:../nested.odocl})))) + (rule + (alias runtest) + (action + (diff nested.targets nested.targets.gen)))) + +(subdir + html + (rule + (targets + Ocamlary.html.gen + Ocamlary-Empty.html.gen + Ocamlary-module-type-Empty.html.gen + Ocamlary-module-type-MissingComment.html.gen + Ocamlary-module-type-EmptySig.html.gen + Ocamlary-ModuleWithSignature.html.gen + Ocamlary-ModuleWithSignatureAlias.html.gen + Ocamlary-One.html.gen + Ocamlary-module-type-SigForMod.html.gen + Ocamlary-module-type-SigForMod-Inner.html.gen + Ocamlary-module-type-SigForMod-Inner-module-type-Empty.html.gen + Ocamlary-module-type-SuperSig.html.gen + Ocamlary-module-type-SuperSig-module-type-SubSigA.html.gen Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html.gen Ocamlary-module-type-SuperSig-module-type-SubSigB.html.gen Ocamlary-module-type-SuperSig-module-type-EmptySig.html.gen @@ -3420,2025 +4779,3496 @@ (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig.html - Ocamlary-module-type-SuperSig.html.gen)) + (diff + Ocamlary-module-type-SuperSig.html + Ocamlary-module-type-SuperSig.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-SuperSig-module-type-SubSigA.html + Ocamlary-module-type-SuperSig-module-type-SubSigA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html + Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-SuperSig-module-type-SubSigB.html + Ocamlary-module-type-SuperSig-module-type-SubSigB.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-SuperSig-module-type-EmptySig.html + Ocamlary-module-type-SuperSig-module-type-EmptySig.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-SuperSig-module-type-One.html + Ocamlary-module-type-SuperSig-module-type-One.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-SuperSig-module-type-SuperSig.html + Ocamlary-module-type-SuperSig-module-type-SuperSig.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Buffer.html Ocamlary-Buffer.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-CollectionModule.html Ocamlary-CollectionModule.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CollectionModule-InnerModuleA.html + Ocamlary-CollectionModule-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html + Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-COLLECTION.html + Ocamlary-module-type-COLLECTION.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-COLLECTION-InnerModuleA.html + Ocamlary-module-type-COLLECTION-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html + Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Recollection.html Ocamlary-Recollection.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-argument-1-C.html + Ocamlary-Recollection-argument-1-C.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-argument-1-C-InnerModuleA.html + Ocamlary-Recollection-argument-1-C-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html + Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-InnerModuleA.html + Ocamlary-Recollection-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html + Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-MMM.html Ocamlary-module-type-MMM.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-MMM-C.html Ocamlary-module-type-MMM-C.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-MMM-C-InnerModuleA.html + Ocamlary-module-type-MMM-C-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html + Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-RECOLLECTION.html + Ocamlary-module-type-RECOLLECTION.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-RecollectionModule.html + Ocamlary-module-type-RecollectionModule.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-RecollectionModule-InnerModuleA.html + Ocamlary-module-type-RecollectionModule-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html + Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-A.html Ocamlary-module-type-A.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-A-Q.html Ocamlary-module-type-A-Q.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-A-Q-InnerModuleA.html + Ocamlary-module-type-A-Q-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html + Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-B.html Ocamlary-module-type-B.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-B-Q.html Ocamlary-module-type-B-Q.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-B-Q-InnerModuleA.html + Ocamlary-module-type-B-Q-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html + Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-C.html Ocamlary-module-type-C.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-C-Q.html Ocamlary-module-type-C-Q.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-C-Q-InnerModuleA.html + Ocamlary-module-type-C-Q-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html + Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-FunctorTypeOf.html Ocamlary-FunctorTypeOf.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-FunctorTypeOf-argument-1-Collection.html + Ocamlary-FunctorTypeOf-argument-1-Collection.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html + Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html + Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html + Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-IncludeModuleType.html + Ocamlary-module-type-IncludeModuleType.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-ToInclude.html + Ocamlary-module-type-ToInclude.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-ToInclude-IncludedA.html + Ocamlary-module-type-ToInclude-IncludedA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-ToInclude-module-type-IncludedB.html + Ocamlary-module-type-ToInclude-module-type-IncludedB.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-IncludedA.html Ocamlary-IncludedA.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-IncludedB.html + Ocamlary-module-type-IncludedB.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-ExtMod.html Ocamlary-ExtMod.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-class-empty_class.html Ocamlary-class-empty_class.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-class-one_method_class.html + Ocamlary-class-one_method_class.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-class-two_method_class.html + Ocamlary-class-two_method_class.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-class-param_class.html Ocamlary-class-param_class.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep1.html Ocamlary-Dep1.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep1-module-type-S.html + Ocamlary-Dep1-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep1-module-type-S-class-c.html + Ocamlary-Dep1-module-type-S-class-c.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep1-X.html Ocamlary-Dep1-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep1-X-Y.html Ocamlary-Dep1-X-Y.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep1-X-Y-class-c.html Ocamlary-Dep1-X-Y-class-c.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep2.html Ocamlary-Dep2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep2-argument-1-Arg.html + Ocamlary-Dep2-argument-1-Arg.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep2-argument-1-Arg-X.html + Ocamlary-Dep2-argument-1-Arg-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep2-A.html Ocamlary-Dep2-A.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep3.html Ocamlary-Dep3.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep4.html Ocamlary-Dep4.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep4-module-type-T.html + Ocamlary-Dep4-module-type-T.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep4-module-type-S.html + Ocamlary-Dep4-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep4-module-type-S-X.html + Ocamlary-Dep4-module-type-S-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep4-module-type-S-Y.html + Ocamlary-Dep4-module-type-S-Y.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep4-X.html Ocamlary-Dep4-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep5.html Ocamlary-Dep5.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep5-argument-1-Arg.html + Ocamlary-Dep5-argument-1-Arg.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep5-argument-1-Arg-module-type-S.html + Ocamlary-Dep5-argument-1-Arg-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep5-argument-1-Arg-module-type-S-Y.html + Ocamlary-Dep5-argument-1-Arg-module-type-S-Y.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep5-Z.html Ocamlary-Dep5-Z.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep6.html Ocamlary-Dep6.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep6-module-type-S.html + Ocamlary-Dep6-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep6-module-type-T.html + Ocamlary-Dep6-module-type-T.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep6-module-type-T-Y.html + Ocamlary-Dep6-module-type-T-Y.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep6-X.html Ocamlary-Dep6-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep6-X-Y.html Ocamlary-Dep6-X-Y.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep7.html Ocamlary-Dep7.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep7-argument-1-Arg.html + Ocamlary-Dep7-argument-1-Arg.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep7-argument-1-Arg-module-type-T.html + Ocamlary-Dep7-argument-1-Arg-module-type-T.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep7-argument-1-Arg-X.html + Ocamlary-Dep7-argument-1-Arg-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep7-M.html Ocamlary-Dep7-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep8.html Ocamlary-Dep8.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep8-module-type-T.html + Ocamlary-Dep8-module-type-T.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep9.html Ocamlary-Dep9.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep9-argument-1-X.html Ocamlary-Dep9-argument-1-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-Dep10.html Ocamlary-module-type-Dep10.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep11.html Ocamlary-Dep11.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep11-module-type-S.html + Ocamlary-Dep11-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep11-module-type-S-class-c.html + Ocamlary-Dep11-module-type-S-class-c.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep12.html Ocamlary-Dep12.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-Dep12-argument-1-Arg.html + Ocamlary-Dep12-argument-1-Arg.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep13.html Ocamlary-Dep13.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Dep13-class-c.html Ocamlary-Dep13-class-c.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-With1.html Ocamlary-module-type-With1.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-With1-M.html + Ocamlary-module-type-With1-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With2.html Ocamlary-With2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With2-module-type-S.html + Ocamlary-With2-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With3.html Ocamlary-With3.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With3-N.html Ocamlary-With3-N.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With4.html Ocamlary-With4.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With4-N.html Ocamlary-With4-N.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With5.html Ocamlary-With5.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With5-module-type-S.html + Ocamlary-With5-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With5-N.html Ocamlary-With5-N.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With6.html Ocamlary-With6.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With6-module-type-T.html + Ocamlary-With6-module-type-T.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With6-module-type-T-M.html + Ocamlary-With6-module-type-T-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With7.html Ocamlary-With7.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With7-argument-1-X.html + Ocamlary-With7-argument-1-X.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-With8.html Ocamlary-module-type-With8.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-With8-M.html + Ocamlary-module-type-With8-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-With8-M-N.html + Ocamlary-module-type-With8-M-N.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With9.html Ocamlary-With9.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With9-module-type-S.html + Ocamlary-With9-module-type-S.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-With10.html Ocamlary-With10.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With10-module-type-T.html + Ocamlary-With10-module-type-T.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-With10-module-type-T-M.html + Ocamlary-With10-module-type-T-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-With11.html + Ocamlary-module-type-With11.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-With11-N.html + Ocamlary-module-type-With11-N.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-NestedInclude1.html + Ocamlary-module-type-NestedInclude1.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html + Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-NestedInclude2.html + Ocamlary-module-type-NestedInclude2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-DoubleInclude1.html Ocamlary-DoubleInclude1.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-DoubleInclude1-DoubleInclude2.html + Ocamlary-DoubleInclude1-DoubleInclude2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-DoubleInclude3.html Ocamlary-DoubleInclude3.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-DoubleInclude3-DoubleInclude2.html + Ocamlary-DoubleInclude3-DoubleInclude2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-IncludeInclude1.html Ocamlary-IncludeInclude1.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html + Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-IncludeInclude1-IncludeInclude2_M.html + Ocamlary-IncludeInclude1-IncludeInclude2_M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-IncludeInclude2.html + Ocamlary-module-type-IncludeInclude2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-IncludeInclude2_M.html Ocamlary-IncludeInclude2_M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-CanonicalTest.html Ocamlary-CanonicalTest.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CanonicalTest-Base.html + Ocamlary-CanonicalTest-Base.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CanonicalTest-Base-List.html + Ocamlary-CanonicalTest-Base-List.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CanonicalTest-Base_Tests.html + Ocamlary-CanonicalTest-Base_Tests.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CanonicalTest-Base_Tests-C.html + Ocamlary-CanonicalTest-Base_Tests-C.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-CanonicalTest-List_modif.html + Ocamlary-CanonicalTest-List_modif.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases.html Ocamlary-Aliases.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Foo.html Ocamlary-Aliases-Foo.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Foo-A.html Ocamlary-Aliases-Foo-A.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Foo-B.html Ocamlary-Aliases-Foo-B.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Foo-C.html Ocamlary-Aliases-Foo-C.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Foo-D.html Ocamlary-Aliases-Foo-D.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Foo-E.html Ocamlary-Aliases-Foo-E.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-Std.html Ocamlary-Aliases-Std.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-E.html Ocamlary-Aliases-E.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-P1.html Ocamlary-Aliases-P1.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-P1-Y.html Ocamlary-Aliases-P1-Y.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Aliases-P2.html Ocamlary-Aliases-P2.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-module-type-M.html Ocamlary-module-type-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-M.html Ocamlary-M.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary-Only_a_module.html Ocamlary-Only_a_module.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-TypeExt.html + Ocamlary-module-type-TypeExt.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary-module-type-TypeExtPruned.html + Ocamlary-module-type-TypeExtPruned.html.gen)) + (enabled_if + (>= %{ocaml_version} 4.07)))) + +(subdir + html + (rule + (action + (with-outputs-to + ocamlary.targets.gen + (run odoc html-targets -o . %{dep:../ocamlary.odocl} --flat))) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff ocamlary.targets ocamlary.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.07)))) + +(subdir + latex + (rule + (targets + Ocamlary.tex.gen + Ocamlary.ModuleWithSignature.tex.gen + Ocamlary.ModuleWithSignatureAlias.tex.gen + Ocamlary.Recollection.tex.gen + Ocamlary.FunctorTypeOf.tex.gen + Ocamlary.empty_class.tex.gen + Ocamlary.one_method_class.tex.gen + Ocamlary.two_method_class.tex.gen + Ocamlary.param_class.tex.gen + Ocamlary.Dep2.tex.gen + Ocamlary.Dep5.tex.gen + Ocamlary.Dep5.Z.tex.gen + Ocamlary.Dep7.tex.gen + Ocamlary.Dep7.M.tex.gen + Ocamlary.Dep9.tex.gen + Ocamlary.Dep12.tex.gen + Ocamlary.Dep13.tex.gen + Ocamlary.Dep13.c.tex.gen + Ocamlary.With3.tex.gen + Ocamlary.With3.N.tex.gen + Ocamlary.With4.tex.gen + Ocamlary.With4.N.tex.gen + Ocamlary.With7.tex.gen) + (action + (run odoc latex-generate -o . --extra-suffix gen %{dep:../ocamlary.odocl})) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.tex Ocamlary.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary.ModuleWithSignature.tex + Ocamlary.ModuleWithSignature.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff + Ocamlary.ModuleWithSignatureAlias.tex + Ocamlary.ModuleWithSignatureAlias.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.Recollection.tex Ocamlary.Recollection.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.FunctorTypeOf.tex Ocamlary.FunctorTypeOf.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.empty_class.tex Ocamlary.empty_class.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.one_method_class.tex Ocamlary.one_method_class.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.two_method_class.tex Ocamlary.two_method_class.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.param_class.tex Ocamlary.param_class.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.Dep2.tex Ocamlary.Dep2.tex.gen)) + (enabled_if + (>= %{ocaml_version} 4.07))) + (rule + (alias runtest) + (action + (diff Ocamlary.Dep5.tex Ocamlary.Dep5.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig-module-type-SubSigA.html - Ocamlary-module-type-SuperSig-module-type-SubSigA.html.gen)) + (diff Ocamlary.Dep5.Z.tex Ocamlary.Dep5.Z.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html - Ocamlary-module-type-SuperSig-module-type-SubSigA-SubSigAMod.html.gen)) + (diff Ocamlary.Dep7.tex Ocamlary.Dep7.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig-module-type-SubSigB.html - Ocamlary-module-type-SuperSig-module-type-SubSigB.html.gen)) + (diff Ocamlary.Dep7.M.tex Ocamlary.Dep7.M.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig-module-type-EmptySig.html - Ocamlary-module-type-SuperSig-module-type-EmptySig.html.gen)) + (diff Ocamlary.Dep9.tex Ocamlary.Dep9.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig-module-type-One.html - Ocamlary-module-type-SuperSig-module-type-One.html.gen)) + (diff Ocamlary.Dep12.tex Ocamlary.Dep12.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-SuperSig-module-type-SuperSig.html - Ocamlary-module-type-SuperSig-module-type-SuperSig.html.gen)) + (diff Ocamlary.Dep13.tex Ocamlary.Dep13.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Buffer.html Ocamlary-Buffer.html.gen)) + (diff Ocamlary.Dep13.c.tex Ocamlary.Dep13.c.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-CollectionModule.html Ocamlary-CollectionModule.html.gen)) + (diff Ocamlary.With3.tex Ocamlary.With3.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-CollectionModule-InnerModuleA.html - Ocamlary-CollectionModule-InnerModuleA.html.gen)) + (diff Ocamlary.With3.N.tex Ocamlary.With3.N.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html - Ocamlary-CollectionModule-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.With4.tex Ocamlary.With4.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-CollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.With4.N.tex Ocamlary.With4.N.tex.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-COLLECTION.html - Ocamlary-module-type-COLLECTION.html.gen)) + (diff Ocamlary.With7.tex Ocamlary.With7.tex.gen)) (enabled_if - (>= %{ocaml_version} 4.07))) + (>= %{ocaml_version} 4.07)))) + +(subdir + latex (rule - (alias runtest) (action - (diff - Ocamlary-module-type-COLLECTION-InnerModuleA.html - Ocamlary-module-type-COLLECTION-InnerModuleA.html.gen)) + (with-outputs-to + ocamlary.targets.gen + (run odoc latex-targets -o . %{dep:../ocamlary.odocl}))) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html - Ocamlary-module-type-COLLECTION-InnerModuleA-InnerModuleA'.html.gen)) + (diff ocamlary.targets ocamlary.targets.gen)) (enabled_if - (>= %{ocaml_version} 4.07))) + (>= %{ocaml_version} 4.07)))) + +(subdir + man (rule - (alias runtest) + (targets + Ocamlary.3o.gen + Ocamlary.Empty.3o.gen + Ocamlary.ModuleWithSignature.3o.gen + Ocamlary.ModuleWithSignatureAlias.3o.gen + Ocamlary.One.3o.gen + Ocamlary.Buffer.3o.gen + Ocamlary.CollectionModule.3o.gen + Ocamlary.CollectionModule.InnerModuleA.3o.gen + Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o.gen + Ocamlary.Recollection.3o.gen + Ocamlary.Recollection.InnerModuleA.3o.gen + Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o.gen + Ocamlary.FunctorTypeOf.3o.gen + Ocamlary.IncludedA.3o.gen + Ocamlary.ExtMod.3o.gen + Ocamlary.empty_class.3o.gen + Ocamlary.one_method_class.3o.gen + Ocamlary.two_method_class.3o.gen + Ocamlary.param_class.3o.gen + Ocamlary.Dep1.3o.gen + Ocamlary.Dep1.X.3o.gen + Ocamlary.Dep1.X.Y.3o.gen + Ocamlary.Dep1.X.Y.c.3o.gen + Ocamlary.Dep2.3o.gen + Ocamlary.Dep2.A.3o.gen + Ocamlary.Dep3.3o.gen + Ocamlary.Dep4.3o.gen + Ocamlary.Dep4.X.3o.gen + Ocamlary.Dep5.3o.gen + Ocamlary.Dep5.Z.3o.gen + Ocamlary.Dep6.3o.gen + Ocamlary.Dep6.X.3o.gen + Ocamlary.Dep6.X.Y.3o.gen + Ocamlary.Dep7.3o.gen + Ocamlary.Dep7.M.3o.gen + Ocamlary.Dep8.3o.gen + Ocamlary.Dep9.3o.gen + Ocamlary.Dep11.3o.gen + Ocamlary.Dep12.3o.gen + Ocamlary.Dep13.3o.gen + Ocamlary.Dep13.c.3o.gen + Ocamlary.With2.3o.gen + Ocamlary.With3.3o.gen + Ocamlary.With3.N.3o.gen + Ocamlary.With4.3o.gen + Ocamlary.With4.N.3o.gen + Ocamlary.With5.3o.gen + Ocamlary.With5.N.3o.gen + Ocamlary.With6.3o.gen + Ocamlary.With7.3o.gen + Ocamlary.With9.3o.gen + Ocamlary.With10.3o.gen + Ocamlary.DoubleInclude1.3o.gen + Ocamlary.DoubleInclude1.DoubleInclude2.3o.gen + Ocamlary.DoubleInclude3.3o.gen + Ocamlary.DoubleInclude3.DoubleInclude2.3o.gen + Ocamlary.IncludeInclude1.3o.gen + Ocamlary.IncludeInclude1.IncludeInclude2_M.3o.gen + Ocamlary.IncludeInclude2_M.3o.gen + Ocamlary.CanonicalTest.3o.gen + Ocamlary.CanonicalTest.Base.3o.gen + Ocamlary.CanonicalTest.Base.List.3o.gen + Ocamlary.CanonicalTest.Base_Tests.3o.gen + Ocamlary.CanonicalTest.Base_Tests.C.3o.gen + Ocamlary.CanonicalTest.List_modif.3o.gen + Ocamlary.Aliases.3o.gen + Ocamlary.Aliases.Foo.3o.gen + Ocamlary.Aliases.Foo.A.3o.gen + Ocamlary.Aliases.Foo.B.3o.gen + Ocamlary.Aliases.Foo.C.3o.gen + Ocamlary.Aliases.Foo.D.3o.gen + Ocamlary.Aliases.Foo.E.3o.gen + Ocamlary.Aliases.Std.3o.gen + Ocamlary.Aliases.E.3o.gen + Ocamlary.Aliases.P1.3o.gen + Ocamlary.Aliases.P1.Y.3o.gen + Ocamlary.Aliases.P2.3o.gen + Ocamlary.M.3o.gen + Ocamlary.Only_a_module.3o.gen) (action - (diff - Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-module-type-COLLECTION-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (run odoc man-generate -o . --extra-suffix gen %{dep:../ocamlary.odocl})) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Recollection.html Ocamlary-Recollection.html.gen)) + (diff Ocamlary.3o Ocamlary.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Recollection-argument-1-C.html - Ocamlary-Recollection-argument-1-C.html.gen)) + (diff Ocamlary.Empty.3o Ocamlary.Empty.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Recollection-argument-1-C-InnerModuleA.html - Ocamlary-Recollection-argument-1-C-InnerModuleA.html.gen)) + (diff Ocamlary.ModuleWithSignature.3o Ocamlary.ModuleWithSignature.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html - Ocamlary-Recollection-argument-1-C-InnerModuleA-InnerModuleA'.html.gen)) + Ocamlary.ModuleWithSignatureAlias.3o + Ocamlary.ModuleWithSignatureAlias.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-Recollection-argument-1-C-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.One.3o Ocamlary.One.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Recollection-InnerModuleA.html - Ocamlary-Recollection-InnerModuleA.html.gen)) + (diff Ocamlary.Buffer.3o Ocamlary.Buffer.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html - Ocamlary-Recollection-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.CollectionModule.3o Ocamlary.CollectionModule.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-Recollection-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + Ocamlary.CollectionModule.InnerModuleA.3o + Ocamlary.CollectionModule.InnerModuleA.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-MMM.html Ocamlary-module-type-MMM.html.gen)) + (diff + Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o + Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-MMM-C.html Ocamlary-module-type-MMM-C.html.gen)) + (diff Ocamlary.Recollection.3o Ocamlary.Recollection.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-MMM-C-InnerModuleA.html - Ocamlary-module-type-MMM-C-InnerModuleA.html.gen)) + Ocamlary.Recollection.InnerModuleA.3o + Ocamlary.Recollection.InnerModuleA.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html - Ocamlary-module-type-MMM-C-InnerModuleA-InnerModuleA'.html.gen)) + Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o + Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-module-type-MMM-C-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.FunctorTypeOf.3o Ocamlary.FunctorTypeOf.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-RECOLLECTION.html - Ocamlary-module-type-RECOLLECTION.html.gen)) + (diff Ocamlary.IncludedA.3o Ocamlary.IncludedA.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-RecollectionModule.html - Ocamlary-module-type-RecollectionModule.html.gen)) + (diff Ocamlary.ExtMod.3o Ocamlary.ExtMod.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-RecollectionModule-InnerModuleA.html - Ocamlary-module-type-RecollectionModule-InnerModuleA.html.gen)) + (diff Ocamlary.empty_class.3o Ocamlary.empty_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html - Ocamlary-module-type-RecollectionModule-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.one_method_class.3o Ocamlary.one_method_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-module-type-RecollectionModule-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.two_method_class.3o Ocamlary.two_method_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-A.html Ocamlary-module-type-A.html.gen)) + (diff Ocamlary.param_class.3o Ocamlary.param_class.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-A-Q.html Ocamlary-module-type-A-Q.html.gen)) + (diff Ocamlary.Dep1.3o Ocamlary.Dep1.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-A-Q-InnerModuleA.html - Ocamlary-module-type-A-Q-InnerModuleA.html.gen)) + (diff Ocamlary.Dep1.X.3o Ocamlary.Dep1.X.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html - Ocamlary-module-type-A-Q-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.Dep1.X.Y.3o Ocamlary.Dep1.X.Y.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-module-type-A-Q-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.Dep1.X.Y.c.3o Ocamlary.Dep1.X.Y.c.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-B.html Ocamlary-module-type-B.html.gen)) + (diff Ocamlary.Dep2.3o Ocamlary.Dep2.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-B-Q.html Ocamlary-module-type-B-Q.html.gen)) + (diff Ocamlary.Dep2.A.3o Ocamlary.Dep2.A.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-B-Q-InnerModuleA.html - Ocamlary-module-type-B-Q-InnerModuleA.html.gen)) + (diff Ocamlary.Dep3.3o Ocamlary.Dep3.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html - Ocamlary-module-type-B-Q-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.Dep4.3o Ocamlary.Dep4.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-module-type-B-Q-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.Dep4.X.3o Ocamlary.Dep4.X.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-C.html Ocamlary-module-type-C.html.gen)) + (diff Ocamlary.Dep5.3o Ocamlary.Dep5.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-C-Q.html Ocamlary-module-type-C-Q.html.gen)) + (diff Ocamlary.Dep5.Z.3o Ocamlary.Dep5.Z.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-C-Q-InnerModuleA.html - Ocamlary-module-type-C-Q-InnerModuleA.html.gen)) + (diff Ocamlary.Dep6.3o Ocamlary.Dep6.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html - Ocamlary-module-type-C-Q-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.Dep6.X.3o Ocamlary.Dep6.X.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-module-type-C-Q-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.Dep6.X.Y.3o Ocamlary.Dep6.X.Y.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-FunctorTypeOf.html Ocamlary-FunctorTypeOf.html.gen)) + (diff Ocamlary.Dep7.3o Ocamlary.Dep7.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-FunctorTypeOf-argument-1-Collection.html - Ocamlary-FunctorTypeOf-argument-1-Collection.html.gen)) + (diff Ocamlary.Dep7.M.3o Ocamlary.Dep7.M.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html - Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA.html.gen)) + (diff Ocamlary.Dep8.3o Ocamlary.Dep8.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html - Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-InnerModuleA'.html.gen)) + (diff Ocamlary.Dep9.3o Ocamlary.Dep9.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html - Ocamlary-FunctorTypeOf-argument-1-Collection-InnerModuleA-module-type-InnerModuleTypeA'.html.gen)) + (diff Ocamlary.Dep11.3o Ocamlary.Dep11.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-IncludeModuleType.html - Ocamlary-module-type-IncludeModuleType.html.gen)) + (diff Ocamlary.Dep12.3o Ocamlary.Dep12.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-ToInclude.html - Ocamlary-module-type-ToInclude.html.gen)) + (diff Ocamlary.Dep13.3o Ocamlary.Dep13.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-ToInclude-IncludedA.html - Ocamlary-module-type-ToInclude-IncludedA.html.gen)) + (diff Ocamlary.Dep13.c.3o Ocamlary.Dep13.c.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-ToInclude-module-type-IncludedB.html - Ocamlary-module-type-ToInclude-module-type-IncludedB.html.gen)) + (diff Ocamlary.With2.3o Ocamlary.With2.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-IncludedA.html Ocamlary-IncludedA.html.gen)) + (diff Ocamlary.With3.3o Ocamlary.With3.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-IncludedB.html - Ocamlary-module-type-IncludedB.html.gen)) + (diff Ocamlary.With3.N.3o Ocamlary.With3.N.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-ExtMod.html Ocamlary-ExtMod.html.gen)) + (diff Ocamlary.With4.3o Ocamlary.With4.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-class-empty_class.html Ocamlary-class-empty_class.html.gen)) + (diff Ocamlary.With4.N.3o Ocamlary.With4.N.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-class-one_method_class.html - Ocamlary-class-one_method_class.html.gen)) + (diff Ocamlary.With5.3o Ocamlary.With5.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-class-two_method_class.html - Ocamlary-class-two_method_class.html.gen)) + (diff Ocamlary.With5.N.3o Ocamlary.With5.N.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-class-param_class.html Ocamlary-class-param_class.html.gen)) + (diff Ocamlary.With6.3o Ocamlary.With6.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep1.html Ocamlary-Dep1.html.gen)) + (diff Ocamlary.With7.3o Ocamlary.With7.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep1-module-type-S.html - Ocamlary-Dep1-module-type-S.html.gen)) + (diff Ocamlary.With9.3o Ocamlary.With9.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep1-module-type-S-class-c.html - Ocamlary-Dep1-module-type-S-class-c.html.gen)) + (diff Ocamlary.With10.3o Ocamlary.With10.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep1-X.html Ocamlary-Dep1-X.html.gen)) + (diff Ocamlary.DoubleInclude1.3o Ocamlary.DoubleInclude1.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep1-X-Y.html Ocamlary-Dep1-X-Y.html.gen)) + (diff + Ocamlary.DoubleInclude1.DoubleInclude2.3o + Ocamlary.DoubleInclude1.DoubleInclude2.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep1-X-Y-class-c.html Ocamlary-Dep1-X-Y-class-c.html.gen)) + (diff Ocamlary.DoubleInclude3.3o Ocamlary.DoubleInclude3.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep2.html Ocamlary-Dep2.html.gen)) + (diff + Ocamlary.DoubleInclude3.DoubleInclude2.3o + Ocamlary.DoubleInclude3.DoubleInclude2.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep2-argument-1-Arg.html - Ocamlary-Dep2-argument-1-Arg.html.gen)) + (diff Ocamlary.IncludeInclude1.3o Ocamlary.IncludeInclude1.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep2-argument-1-Arg-X.html - Ocamlary-Dep2-argument-1-Arg-X.html.gen)) + Ocamlary.IncludeInclude1.IncludeInclude2_M.3o + Ocamlary.IncludeInclude1.IncludeInclude2_M.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep2-A.html Ocamlary-Dep2-A.html.gen)) + (diff Ocamlary.IncludeInclude2_M.3o Ocamlary.IncludeInclude2_M.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep3.html Ocamlary-Dep3.html.gen)) + (diff Ocamlary.CanonicalTest.3o Ocamlary.CanonicalTest.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep4.html Ocamlary-Dep4.html.gen)) + (diff Ocamlary.CanonicalTest.Base.3o Ocamlary.CanonicalTest.Base.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep4-module-type-T.html - Ocamlary-Dep4-module-type-T.html.gen)) + Ocamlary.CanonicalTest.Base.List.3o + Ocamlary.CanonicalTest.Base.List.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep4-module-type-S.html - Ocamlary-Dep4-module-type-S.html.gen)) + Ocamlary.CanonicalTest.Base_Tests.3o + Ocamlary.CanonicalTest.Base_Tests.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep4-module-type-S-X.html - Ocamlary-Dep4-module-type-S-X.html.gen)) + Ocamlary.CanonicalTest.Base_Tests.C.3o + Ocamlary.CanonicalTest.Base_Tests.C.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep4-module-type-S-Y.html - Ocamlary-Dep4-module-type-S-Y.html.gen)) + Ocamlary.CanonicalTest.List_modif.3o + Ocamlary.CanonicalTest.List_modif.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep4-X.html Ocamlary-Dep4-X.html.gen)) + (diff Ocamlary.Aliases.3o Ocamlary.Aliases.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep5.html Ocamlary-Dep5.html.gen)) + (diff Ocamlary.Aliases.Foo.3o Ocamlary.Aliases.Foo.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep5-argument-1-Arg.html - Ocamlary-Dep5-argument-1-Arg.html.gen)) + (diff Ocamlary.Aliases.Foo.A.3o Ocamlary.Aliases.Foo.A.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep5-argument-1-Arg-module-type-S.html - Ocamlary-Dep5-argument-1-Arg-module-type-S.html.gen)) + (diff Ocamlary.Aliases.Foo.B.3o Ocamlary.Aliases.Foo.B.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep5-argument-1-Arg-module-type-S-Y.html - Ocamlary-Dep5-argument-1-Arg-module-type-S-Y.html.gen)) + (diff Ocamlary.Aliases.Foo.C.3o Ocamlary.Aliases.Foo.C.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep5-Z.html Ocamlary-Dep5-Z.html.gen)) + (diff Ocamlary.Aliases.Foo.D.3o Ocamlary.Aliases.Foo.D.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep6.html Ocamlary-Dep6.html.gen)) + (diff Ocamlary.Aliases.Foo.E.3o Ocamlary.Aliases.Foo.E.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep6-module-type-S.html - Ocamlary-Dep6-module-type-S.html.gen)) + (diff Ocamlary.Aliases.Std.3o Ocamlary.Aliases.Std.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep6-module-type-T.html - Ocamlary-Dep6-module-type-T.html.gen)) + (diff Ocamlary.Aliases.E.3o Ocamlary.Aliases.E.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep6-module-type-T-Y.html - Ocamlary-Dep6-module-type-T-Y.html.gen)) + (diff Ocamlary.Aliases.P1.3o Ocamlary.Aliases.P1.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep6-X.html Ocamlary-Dep6-X.html.gen)) + (diff Ocamlary.Aliases.P1.Y.3o Ocamlary.Aliases.P1.Y.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep6-X-Y.html Ocamlary-Dep6-X-Y.html.gen)) + (diff Ocamlary.Aliases.P2.3o Ocamlary.Aliases.P2.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep7.html Ocamlary-Dep7.html.gen)) + (diff Ocamlary.M.3o Ocamlary.M.3o.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep7-argument-1-Arg.html - Ocamlary-Dep7-argument-1-Arg.html.gen)) + (diff Ocamlary.Only_a_module.3o Ocamlary.Only_a_module.3o.gen)) (enabled_if - (>= %{ocaml_version} 4.07))) + (>= %{ocaml_version} 4.07)))) + +(subdir + man (rule - (alias runtest) (action - (diff - Ocamlary-Dep7-argument-1-Arg-module-type-T.html - Ocamlary-Dep7-argument-1-Arg-module-type-T.html.gen)) + (with-outputs-to + ocamlary.targets.gen + (run odoc man-targets -o . %{dep:../ocamlary.odocl}))) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep7-argument-1-Arg-X.html - Ocamlary-Dep7-argument-1-Arg-X.html.gen)) + (diff ocamlary.targets ocamlary.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.07)))) + +(subdir + markdown + (rule + (targets + Ocamlary.md.gen + Ocamlary.Empty.md.gen + Ocamlary.module-type-Empty.md.gen + Ocamlary.module-type-MissingComment.md.gen + Ocamlary.module-type-EmptySig.md.gen + Ocamlary.ModuleWithSignature.md.gen + Ocamlary.ModuleWithSignatureAlias.md.gen + Ocamlary.One.md.gen + Ocamlary.module-type-SigForMod.md.gen + Ocamlary.module-type-SigForMod.Inner.md.gen + Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md.gen + Ocamlary.module-type-SuperSig.md.gen + Ocamlary.module-type-SuperSig.module-type-SubSigA.md.gen + Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md.gen + Ocamlary.module-type-SuperSig.module-type-SubSigB.md.gen + Ocamlary.module-type-SuperSig.module-type-EmptySig.md.gen + Ocamlary.module-type-SuperSig.module-type-One.md.gen + Ocamlary.module-type-SuperSig.module-type-SuperSig.md.gen + Ocamlary.Buffer.md.gen + Ocamlary.CollectionModule.md.gen + Ocamlary.CollectionModule.InnerModuleA.md.gen + Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-COLLECTION.md.gen + Ocamlary.module-type-COLLECTION.InnerModuleA.md.gen + Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.Recollection.md.gen + Ocamlary.Recollection.argument-1-C.md.gen + Ocamlary.Recollection.argument-1-C.InnerModuleA.md.gen + Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.Recollection.InnerModuleA.md.gen + Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-MMM.md.gen + Ocamlary.module-type-MMM.C.md.gen + Ocamlary.module-type-MMM.C.InnerModuleA.md.gen + Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-RECOLLECTION.md.gen + Ocamlary.module-type-RecollectionModule.md.gen + Ocamlary.module-type-RecollectionModule.InnerModuleA.md.gen + Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-A.md.gen + Ocamlary.module-type-A.Q.md.gen + Ocamlary.module-type-A.Q.InnerModuleA.md.gen + Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-B.md.gen + Ocamlary.module-type-B.Q.md.gen + Ocamlary.module-type-B.Q.InnerModuleA.md.gen + Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-C.md.gen + Ocamlary.module-type-C.Q.md.gen + Ocamlary.module-type-C.Q.InnerModuleA.md.gen + Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.FunctorTypeOf.md.gen + Ocamlary.FunctorTypeOf.argument-1-Collection.md.gen + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md.gen + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md.gen + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md.gen + Ocamlary.module-type-IncludeModuleType.md.gen + Ocamlary.module-type-ToInclude.md.gen + Ocamlary.module-type-ToInclude.IncludedA.md.gen + Ocamlary.module-type-ToInclude.module-type-IncludedB.md.gen + Ocamlary.IncludedA.md.gen + Ocamlary.module-type-IncludedB.md.gen + Ocamlary.ExtMod.md.gen + Ocamlary.empty_class.md.gen + Ocamlary.one_method_class.md.gen + Ocamlary.two_method_class.md.gen + Ocamlary.param_class.md.gen + Ocamlary.Dep1.md.gen + Ocamlary.Dep1.module-type-S.md.gen + Ocamlary.Dep1.module-type-S.c.md.gen + Ocamlary.Dep1.X.md.gen + Ocamlary.Dep1.X.Y.md.gen + Ocamlary.Dep1.X.Y.c.md.gen + Ocamlary.Dep2.md.gen + Ocamlary.Dep2.argument-1-Arg.md.gen + Ocamlary.Dep2.argument-1-Arg.X.md.gen + Ocamlary.Dep2.A.md.gen + Ocamlary.Dep3.md.gen + Ocamlary.Dep4.md.gen + Ocamlary.Dep4.module-type-T.md.gen + Ocamlary.Dep4.module-type-S.md.gen + Ocamlary.Dep4.module-type-S.X.md.gen + Ocamlary.Dep4.module-type-S.Y.md.gen + Ocamlary.Dep4.X.md.gen + Ocamlary.Dep5.md.gen + Ocamlary.Dep5.argument-1-Arg.md.gen + Ocamlary.Dep5.argument-1-Arg.module-type-S.md.gen + Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md.gen + Ocamlary.Dep5.Z.md.gen + Ocamlary.Dep6.md.gen + Ocamlary.Dep6.module-type-S.md.gen + Ocamlary.Dep6.module-type-T.md.gen + Ocamlary.Dep6.module-type-T.Y.md.gen + Ocamlary.Dep6.X.md.gen + Ocamlary.Dep6.X.Y.md.gen + Ocamlary.Dep7.md.gen + Ocamlary.Dep7.argument-1-Arg.md.gen + Ocamlary.Dep7.argument-1-Arg.module-type-T.md.gen + Ocamlary.Dep7.argument-1-Arg.X.md.gen + Ocamlary.Dep7.M.md.gen + Ocamlary.Dep8.md.gen + Ocamlary.Dep8.module-type-T.md.gen + Ocamlary.Dep9.md.gen + Ocamlary.Dep9.argument-1-X.md.gen + Ocamlary.module-type-Dep10.md.gen + Ocamlary.Dep11.md.gen + Ocamlary.Dep11.module-type-S.md.gen + Ocamlary.Dep11.module-type-S.c.md.gen + Ocamlary.Dep12.md.gen + Ocamlary.Dep12.argument-1-Arg.md.gen + Ocamlary.Dep13.md.gen + Ocamlary.Dep13.c.md.gen + Ocamlary.module-type-With1.md.gen + Ocamlary.module-type-With1.M.md.gen + Ocamlary.With2.md.gen + Ocamlary.With2.module-type-S.md.gen + Ocamlary.With3.md.gen + Ocamlary.With3.N.md.gen + Ocamlary.With4.md.gen + Ocamlary.With4.N.md.gen + Ocamlary.With5.md.gen + Ocamlary.With5.module-type-S.md.gen + Ocamlary.With5.N.md.gen + Ocamlary.With6.md.gen + Ocamlary.With6.module-type-T.md.gen + Ocamlary.With6.module-type-T.M.md.gen + Ocamlary.With7.md.gen + Ocamlary.With7.argument-1-X.md.gen + Ocamlary.module-type-With8.md.gen + Ocamlary.module-type-With8.M.md.gen + Ocamlary.module-type-With8.M.N.md.gen + Ocamlary.With9.md.gen + Ocamlary.With9.module-type-S.md.gen + Ocamlary.With10.md.gen + Ocamlary.With10.module-type-T.md.gen + Ocamlary.With10.module-type-T.M.md.gen + Ocamlary.module-type-With11.md.gen + Ocamlary.module-type-With11.N.md.gen + Ocamlary.module-type-NestedInclude1.md.gen + Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md.gen + Ocamlary.module-type-NestedInclude2.md.gen + Ocamlary.DoubleInclude1.md.gen + Ocamlary.DoubleInclude1.DoubleInclude2.md.gen + Ocamlary.DoubleInclude3.md.gen + Ocamlary.DoubleInclude3.DoubleInclude2.md.gen + Ocamlary.IncludeInclude1.md.gen + Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md.gen + Ocamlary.IncludeInclude1.IncludeInclude2_M.md.gen + Ocamlary.module-type-IncludeInclude2.md.gen + Ocamlary.IncludeInclude2_M.md.gen + Ocamlary.CanonicalTest.md.gen + Ocamlary.CanonicalTest.Base.md.gen + Ocamlary.CanonicalTest.Base.List.md.gen + Ocamlary.CanonicalTest.Base_Tests.md.gen + Ocamlary.CanonicalTest.Base_Tests.C.md.gen + Ocamlary.CanonicalTest.List_modif.md.gen + Ocamlary.Aliases.md.gen + Ocamlary.Aliases.Foo.md.gen + Ocamlary.Aliases.Foo.A.md.gen + Ocamlary.Aliases.Foo.B.md.gen + Ocamlary.Aliases.Foo.C.md.gen + Ocamlary.Aliases.Foo.D.md.gen + Ocamlary.Aliases.Foo.E.md.gen + Ocamlary.Aliases.Std.md.gen + Ocamlary.Aliases.E.md.gen + Ocamlary.Aliases.P1.md.gen + Ocamlary.Aliases.P1.Y.md.gen + Ocamlary.Aliases.P2.md.gen + Ocamlary.module-type-M.md.gen + Ocamlary.M.md.gen + Ocamlary.Only_a_module.md.gen + Ocamlary.module-type-TypeExt.md.gen + Ocamlary.module-type-TypeExtPruned.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../ocamlary.odocl})) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep7-M.html Ocamlary-Dep7-M.html.gen)) + (diff Ocamlary.md Ocamlary.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep8.html Ocamlary-Dep8.html.gen)) + (diff Ocamlary.Empty.md Ocamlary.Empty.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep8-module-type-T.html - Ocamlary-Dep8-module-type-T.html.gen)) + (diff Ocamlary.module-type-Empty.md Ocamlary.module-type-Empty.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep9.html Ocamlary-Dep9.html.gen)) + (diff + Ocamlary.module-type-MissingComment.md + Ocamlary.module-type-MissingComment.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep9-argument-1-X.html Ocamlary-Dep9-argument-1-X.html.gen)) + (diff + Ocamlary.module-type-EmptySig.md + Ocamlary.module-type-EmptySig.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-Dep10.html Ocamlary-module-type-Dep10.html.gen)) + (diff Ocamlary.ModuleWithSignature.md Ocamlary.ModuleWithSignature.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep11.html Ocamlary-Dep11.html.gen)) + (diff + Ocamlary.ModuleWithSignatureAlias.md + Ocamlary.ModuleWithSignatureAlias.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-Dep11-module-type-S.html - Ocamlary-Dep11-module-type-S.html.gen)) + (diff Ocamlary.One.md Ocamlary.One.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep11-module-type-S-class-c.html - Ocamlary-Dep11-module-type-S-class-c.html.gen)) + Ocamlary.module-type-SigForMod.md + Ocamlary.module-type-SigForMod.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep12.html Ocamlary-Dep12.html.gen)) + (diff + Ocamlary.module-type-SigForMod.Inner.md + Ocamlary.module-type-SigForMod.Inner.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-Dep12-argument-1-Arg.html - Ocamlary-Dep12-argument-1-Arg.html.gen)) + Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md + Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep13.html Ocamlary-Dep13.html.gen)) + (diff + Ocamlary.module-type-SuperSig.md + Ocamlary.module-type-SuperSig.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Dep13-class-c.html Ocamlary-Dep13-class-c.html.gen)) + (diff + Ocamlary.module-type-SuperSig.module-type-SubSigA.md + Ocamlary.module-type-SuperSig.module-type-SubSigA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-With1.html Ocamlary-module-type-With1.html.gen)) + (diff + Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md + Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-With1-M.html - Ocamlary-module-type-With1-M.html.gen)) + Ocamlary.module-type-SuperSig.module-type-SubSigB.md + Ocamlary.module-type-SuperSig.module-type-SubSigB.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With2.html Ocamlary-With2.html.gen)) + (diff + Ocamlary.module-type-SuperSig.module-type-EmptySig.md + Ocamlary.module-type-SuperSig.module-type-EmptySig.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-With2-module-type-S.html - Ocamlary-With2-module-type-S.html.gen)) + Ocamlary.module-type-SuperSig.module-type-One.md + Ocamlary.module-type-SuperSig.module-type-One.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With3.html Ocamlary-With3.html.gen)) + (diff + Ocamlary.module-type-SuperSig.module-type-SuperSig.md + Ocamlary.module-type-SuperSig.module-type-SuperSig.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With3-N.html Ocamlary-With3-N.html.gen)) + (diff Ocamlary.Buffer.md Ocamlary.Buffer.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With4.html Ocamlary-With4.html.gen)) + (diff Ocamlary.CollectionModule.md Ocamlary.CollectionModule.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With4-N.html Ocamlary-With4-N.html.gen)) + (diff + Ocamlary.CollectionModule.InnerModuleA.md + Ocamlary.CollectionModule.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With5.html Ocamlary-With5.html.gen)) + (diff + Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md + Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-With5-module-type-S.html - Ocamlary-With5-module-type-S.html.gen)) + Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With5-N.html Ocamlary-With5-N.html.gen)) + (diff + Ocamlary.module-type-COLLECTION.md + Ocamlary.module-type-COLLECTION.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With6.html Ocamlary-With6.html.gen)) + (diff + Ocamlary.module-type-COLLECTION.InnerModuleA.md + Ocamlary.module-type-COLLECTION.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-With6-module-type-T.html - Ocamlary-With6-module-type-T.html.gen)) + Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md + Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-With6-module-type-T-M.html - Ocamlary-With6-module-type-T-M.html.gen)) + Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With7.html Ocamlary-With7.html.gen)) + (diff Ocamlary.Recollection.md Ocamlary.Recollection.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-With7-argument-1-X.html - Ocamlary-With7-argument-1-X.html.gen)) + Ocamlary.Recollection.argument-1-C.md + Ocamlary.Recollection.argument-1-C.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-With8.html Ocamlary-module-type-With8.html.gen)) + (diff + Ocamlary.Recollection.argument-1-C.InnerModuleA.md + Ocamlary.Recollection.argument-1-C.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-With8-M.html - Ocamlary-module-type-With8-M.html.gen)) + Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md + Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-With8-M-N.html - Ocamlary-module-type-With8-M-N.html.gen)) + Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With9.html Ocamlary-With9.html.gen)) + (diff + Ocamlary.Recollection.InnerModuleA.md + Ocamlary.Recollection.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-With9-module-type-S.html - Ocamlary-With9-module-type-S.html.gen)) + Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md + Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-With10.html Ocamlary-With10.html.gen)) + (diff + Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-With10-module-type-T.html - Ocamlary-With10-module-type-T.html.gen)) + (diff Ocamlary.module-type-MMM.md Ocamlary.module-type-MMM.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-With10-module-type-T-M.html - Ocamlary-With10-module-type-T-M.html.gen)) + (diff Ocamlary.module-type-MMM.C.md Ocamlary.module-type-MMM.C.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-With11.html - Ocamlary-module-type-With11.html.gen)) + Ocamlary.module-type-MMM.C.InnerModuleA.md + Ocamlary.module-type-MMM.C.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-With11-N.html - Ocamlary-module-type-With11-N.html.gen)) + Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md + Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-NestedInclude1.html - Ocamlary-module-type-NestedInclude1.html.gen)) + Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html - Ocamlary-module-type-NestedInclude1-module-type-NestedInclude2.html.gen)) + Ocamlary.module-type-RECOLLECTION.md + Ocamlary.module-type-RECOLLECTION.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-NestedInclude2.html - Ocamlary-module-type-NestedInclude2.html.gen)) + Ocamlary.module-type-RecollectionModule.md + Ocamlary.module-type-RecollectionModule.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-DoubleInclude1.html Ocamlary-DoubleInclude1.html.gen)) + (diff + Ocamlary.module-type-RecollectionModule.InnerModuleA.md + Ocamlary.module-type-RecollectionModule.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-DoubleInclude1-DoubleInclude2.html - Ocamlary-DoubleInclude1-DoubleInclude2.html.gen)) + Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md + Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-DoubleInclude3.html Ocamlary-DoubleInclude3.html.gen)) + (diff + Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-DoubleInclude3-DoubleInclude2.html - Ocamlary-DoubleInclude3-DoubleInclude2.html.gen)) + (diff Ocamlary.module-type-A.md Ocamlary.module-type-A.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-IncludeInclude1.html Ocamlary-IncludeInclude1.html.gen)) + (diff Ocamlary.module-type-A.Q.md Ocamlary.module-type-A.Q.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html - Ocamlary-IncludeInclude1-module-type-IncludeInclude2.html.gen)) + Ocamlary.module-type-A.Q.InnerModuleA.md + Ocamlary.module-type-A.Q.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-IncludeInclude1-IncludeInclude2_M.html - Ocamlary-IncludeInclude1-IncludeInclude2_M.html.gen)) + Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md + Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-module-type-IncludeInclude2.html - Ocamlary-module-type-IncludeInclude2.html.gen)) + Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-IncludeInclude2_M.html Ocamlary-IncludeInclude2_M.html.gen)) + (diff Ocamlary.module-type-B.md Ocamlary.module-type-B.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-CanonicalTest.html Ocamlary-CanonicalTest.html.gen)) + (diff Ocamlary.module-type-B.Q.md Ocamlary.module-type-B.Q.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-CanonicalTest-Base.html - Ocamlary-CanonicalTest-Base.html.gen)) + Ocamlary.module-type-B.Q.InnerModuleA.md + Ocamlary.module-type-B.Q.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-CanonicalTest-Base-List.html - Ocamlary-CanonicalTest-Base-List.html.gen)) + Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md + Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary-CanonicalTest-Base_Tests.html - Ocamlary-CanonicalTest-Base_Tests.html.gen)) + Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-CanonicalTest-Base_Tests-C.html - Ocamlary-CanonicalTest-Base_Tests-C.html.gen)) + (diff Ocamlary.module-type-C.md Ocamlary.module-type-C.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-CanonicalTest-List_modif.html - Ocamlary-CanonicalTest-List_modif.html.gen)) + (diff Ocamlary.module-type-C.Q.md Ocamlary.module-type-C.Q.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases.html Ocamlary-Aliases.html.gen)) + (diff + Ocamlary.module-type-C.Q.InnerModuleA.md + Ocamlary.module-type-C.Q.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Foo.html Ocamlary-Aliases-Foo.html.gen)) + (diff + Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md + Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Foo-A.html Ocamlary-Aliases-Foo-A.html.gen)) + (diff + Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Foo-B.html Ocamlary-Aliases-Foo-B.html.gen)) + (diff Ocamlary.FunctorTypeOf.md Ocamlary.FunctorTypeOf.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Foo-C.html Ocamlary-Aliases-Foo-C.html.gen)) + (diff + Ocamlary.FunctorTypeOf.argument-1-Collection.md + Ocamlary.FunctorTypeOf.argument-1-Collection.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Foo-D.html Ocamlary-Aliases-Foo-D.html.gen)) + (diff + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Foo-E.html Ocamlary-Aliases-Foo-E.html.gen)) + (diff + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-Std.html Ocamlary-Aliases-Std.html.gen)) + (diff + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md + Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-E.html Ocamlary-Aliases-E.html.gen)) + (diff + Ocamlary.module-type-IncludeModuleType.md + Ocamlary.module-type-IncludeModuleType.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-P1.html Ocamlary-Aliases-P1.html.gen)) + (diff + Ocamlary.module-type-ToInclude.md + Ocamlary.module-type-ToInclude.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-P1-Y.html Ocamlary-Aliases-P1-Y.html.gen)) + (diff + Ocamlary.module-type-ToInclude.IncludedA.md + Ocamlary.module-type-ToInclude.IncludedA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Aliases-P2.html Ocamlary-Aliases-P2.html.gen)) + (diff + Ocamlary.module-type-ToInclude.module-type-IncludedB.md + Ocamlary.module-type-ToInclude.module-type-IncludedB.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-module-type-M.html Ocamlary-module-type-M.html.gen)) + (diff Ocamlary.IncludedA.md Ocamlary.IncludedA.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-M.html Ocamlary-M.html.gen)) + (diff + Ocamlary.module-type-IncludedB.md + Ocamlary.module-type-IncludedB.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary-Only_a_module.html Ocamlary-Only_a_module.html.gen)) + (diff Ocamlary.ExtMod.md Ocamlary.ExtMod.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-TypeExt.html - Ocamlary-module-type-TypeExt.html.gen)) + (diff Ocamlary.empty_class.md Ocamlary.empty_class.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary-module-type-TypeExtPruned.html - Ocamlary-module-type-TypeExtPruned.html.gen)) + (diff Ocamlary.one_method_class.md Ocamlary.one_method_class.md.gen)) (enabled_if - (>= %{ocaml_version} 4.07)))) - -(subdir - html + (>= %{ocaml_version} 4.07))) (rule + (alias runtest) (action - (with-outputs-to - ocamlary.targets.gen - (run odoc html-targets -o . %{dep:../ocamlary.odocl} --flat))) + (diff Ocamlary.two_method_class.md Ocamlary.two_method_class.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff ocamlary.targets ocamlary.targets.gen)) + (diff Ocamlary.param_class.md Ocamlary.param_class.md.gen)) (enabled_if - (>= %{ocaml_version} 4.07)))) - -(subdir - latex + (>= %{ocaml_version} 4.07))) (rule - (targets - Ocamlary.tex.gen - Ocamlary.ModuleWithSignature.tex.gen - Ocamlary.ModuleWithSignatureAlias.tex.gen - Ocamlary.Recollection.tex.gen - Ocamlary.FunctorTypeOf.tex.gen - Ocamlary.empty_class.tex.gen - Ocamlary.one_method_class.tex.gen - Ocamlary.two_method_class.tex.gen - Ocamlary.param_class.tex.gen - Ocamlary.Dep2.tex.gen - Ocamlary.Dep5.tex.gen - Ocamlary.Dep5.Z.tex.gen - Ocamlary.Dep7.tex.gen - Ocamlary.Dep7.M.tex.gen - Ocamlary.Dep9.tex.gen - Ocamlary.Dep12.tex.gen - Ocamlary.Dep13.tex.gen - Ocamlary.Dep13.c.tex.gen - Ocamlary.With3.tex.gen - Ocamlary.With3.N.tex.gen - Ocamlary.With4.tex.gen - Ocamlary.With4.N.tex.gen - Ocamlary.With7.tex.gen) + (alias runtest) (action - (run odoc latex-generate -o . --extra-suffix gen %{dep:../ocamlary.odocl})) + (diff Ocamlary.Dep1.md Ocamlary.Dep1.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.tex Ocamlary.tex.gen)) + (diff Ocamlary.Dep1.module-type-S.md Ocamlary.Dep1.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary.ModuleWithSignature.tex - Ocamlary.ModuleWithSignature.tex.gen)) + Ocamlary.Dep1.module-type-S.c.md + Ocamlary.Dep1.module-type-S.c.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.ModuleWithSignatureAlias.tex - Ocamlary.ModuleWithSignatureAlias.tex.gen)) + (diff Ocamlary.Dep1.X.md Ocamlary.Dep1.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Recollection.tex Ocamlary.Recollection.tex.gen)) + (diff Ocamlary.Dep1.X.Y.md Ocamlary.Dep1.X.Y.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.FunctorTypeOf.tex Ocamlary.FunctorTypeOf.tex.gen)) + (diff Ocamlary.Dep1.X.Y.c.md Ocamlary.Dep1.X.Y.c.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.empty_class.tex Ocamlary.empty_class.tex.gen)) + (diff Ocamlary.Dep2.md Ocamlary.Dep2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.one_method_class.tex Ocamlary.one_method_class.tex.gen)) + (diff Ocamlary.Dep2.argument-1-Arg.md Ocamlary.Dep2.argument-1-Arg.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.two_method_class.tex Ocamlary.two_method_class.tex.gen)) + (diff + Ocamlary.Dep2.argument-1-Arg.X.md + Ocamlary.Dep2.argument-1-Arg.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.param_class.tex Ocamlary.param_class.tex.gen)) + (diff Ocamlary.Dep2.A.md Ocamlary.Dep2.A.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep2.tex Ocamlary.Dep2.tex.gen)) + (diff Ocamlary.Dep3.md Ocamlary.Dep3.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep5.tex Ocamlary.Dep5.tex.gen)) + (diff Ocamlary.Dep4.md Ocamlary.Dep4.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep5.Z.tex Ocamlary.Dep5.Z.tex.gen)) + (diff Ocamlary.Dep4.module-type-T.md Ocamlary.Dep4.module-type-T.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep7.tex Ocamlary.Dep7.tex.gen)) + (diff Ocamlary.Dep4.module-type-S.md Ocamlary.Dep4.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep7.M.tex Ocamlary.Dep7.M.tex.gen)) + (diff + Ocamlary.Dep4.module-type-S.X.md + Ocamlary.Dep4.module-type-S.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep9.tex Ocamlary.Dep9.tex.gen)) + (diff + Ocamlary.Dep4.module-type-S.Y.md + Ocamlary.Dep4.module-type-S.Y.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep12.tex Ocamlary.Dep12.tex.gen)) + (diff Ocamlary.Dep4.X.md Ocamlary.Dep4.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep13.tex Ocamlary.Dep13.tex.gen)) + (diff Ocamlary.Dep5.md Ocamlary.Dep5.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep13.c.tex Ocamlary.Dep13.c.tex.gen)) + (diff Ocamlary.Dep5.argument-1-Arg.md Ocamlary.Dep5.argument-1-Arg.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With3.tex Ocamlary.With3.tex.gen)) + (diff + Ocamlary.Dep5.argument-1-Arg.module-type-S.md + Ocamlary.Dep5.argument-1-Arg.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With3.N.tex Ocamlary.With3.N.tex.gen)) + (diff + Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md + Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With4.tex Ocamlary.With4.tex.gen)) + (diff Ocamlary.Dep5.Z.md Ocamlary.Dep5.Z.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With4.N.tex Ocamlary.With4.N.tex.gen)) + (diff Ocamlary.Dep6.md Ocamlary.Dep6.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With7.tex Ocamlary.With7.tex.gen)) + (diff Ocamlary.Dep6.module-type-S.md Ocamlary.Dep6.module-type-S.md.gen)) (enabled_if - (>= %{ocaml_version} 4.07)))) - -(subdir - latex + (>= %{ocaml_version} 4.07))) (rule + (alias runtest) (action - (with-outputs-to - ocamlary.targets.gen - (run odoc latex-targets -o . %{dep:../ocamlary.odocl}))) + (diff Ocamlary.Dep6.module-type-T.md Ocamlary.Dep6.module-type-T.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff ocamlary.targets ocamlary.targets.gen)) + (diff + Ocamlary.Dep6.module-type-T.Y.md + Ocamlary.Dep6.module-type-T.Y.md.gen)) (enabled_if - (>= %{ocaml_version} 4.07)))) - -(subdir - man + (>= %{ocaml_version} 4.07))) (rule - (targets - Ocamlary.3o.gen - Ocamlary.Empty.3o.gen - Ocamlary.ModuleWithSignature.3o.gen - Ocamlary.ModuleWithSignatureAlias.3o.gen - Ocamlary.One.3o.gen - Ocamlary.Buffer.3o.gen - Ocamlary.CollectionModule.3o.gen - Ocamlary.CollectionModule.InnerModuleA.3o.gen - Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o.gen - Ocamlary.Recollection.3o.gen - Ocamlary.Recollection.InnerModuleA.3o.gen - Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o.gen - Ocamlary.FunctorTypeOf.3o.gen - Ocamlary.IncludedA.3o.gen - Ocamlary.ExtMod.3o.gen - Ocamlary.empty_class.3o.gen - Ocamlary.one_method_class.3o.gen - Ocamlary.two_method_class.3o.gen - Ocamlary.param_class.3o.gen - Ocamlary.Dep1.3o.gen - Ocamlary.Dep1.X.3o.gen - Ocamlary.Dep1.X.Y.3o.gen - Ocamlary.Dep1.X.Y.c.3o.gen - Ocamlary.Dep2.3o.gen - Ocamlary.Dep2.A.3o.gen - Ocamlary.Dep3.3o.gen - Ocamlary.Dep4.3o.gen - Ocamlary.Dep4.X.3o.gen - Ocamlary.Dep5.3o.gen - Ocamlary.Dep5.Z.3o.gen - Ocamlary.Dep6.3o.gen - Ocamlary.Dep6.X.3o.gen - Ocamlary.Dep6.X.Y.3o.gen - Ocamlary.Dep7.3o.gen - Ocamlary.Dep7.M.3o.gen - Ocamlary.Dep8.3o.gen - Ocamlary.Dep9.3o.gen - Ocamlary.Dep11.3o.gen - Ocamlary.Dep12.3o.gen - Ocamlary.Dep13.3o.gen - Ocamlary.Dep13.c.3o.gen - Ocamlary.With2.3o.gen - Ocamlary.With3.3o.gen - Ocamlary.With3.N.3o.gen - Ocamlary.With4.3o.gen - Ocamlary.With4.N.3o.gen - Ocamlary.With5.3o.gen - Ocamlary.With5.N.3o.gen - Ocamlary.With6.3o.gen - Ocamlary.With7.3o.gen - Ocamlary.With9.3o.gen - Ocamlary.With10.3o.gen - Ocamlary.DoubleInclude1.3o.gen - Ocamlary.DoubleInclude1.DoubleInclude2.3o.gen - Ocamlary.DoubleInclude3.3o.gen - Ocamlary.DoubleInclude3.DoubleInclude2.3o.gen - Ocamlary.IncludeInclude1.3o.gen - Ocamlary.IncludeInclude1.IncludeInclude2_M.3o.gen - Ocamlary.IncludeInclude2_M.3o.gen - Ocamlary.CanonicalTest.3o.gen - Ocamlary.CanonicalTest.Base.3o.gen - Ocamlary.CanonicalTest.Base.List.3o.gen - Ocamlary.CanonicalTest.Base_Tests.3o.gen - Ocamlary.CanonicalTest.Base_Tests.C.3o.gen - Ocamlary.CanonicalTest.List_modif.3o.gen - Ocamlary.Aliases.3o.gen - Ocamlary.Aliases.Foo.3o.gen - Ocamlary.Aliases.Foo.A.3o.gen - Ocamlary.Aliases.Foo.B.3o.gen - Ocamlary.Aliases.Foo.C.3o.gen - Ocamlary.Aliases.Foo.D.3o.gen - Ocamlary.Aliases.Foo.E.3o.gen - Ocamlary.Aliases.Std.3o.gen - Ocamlary.Aliases.E.3o.gen - Ocamlary.Aliases.P1.3o.gen - Ocamlary.Aliases.P1.Y.3o.gen - Ocamlary.Aliases.P2.3o.gen - Ocamlary.M.3o.gen - Ocamlary.Only_a_module.3o.gen) + (alias runtest) (action - (run odoc man-generate -o . --extra-suffix gen %{dep:../ocamlary.odocl})) + (diff Ocamlary.Dep6.X.md Ocamlary.Dep6.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.3o Ocamlary.3o.gen)) + (diff Ocamlary.Dep6.X.Y.md Ocamlary.Dep6.X.Y.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Empty.3o Ocamlary.Empty.3o.gen)) + (diff Ocamlary.Dep7.md Ocamlary.Dep7.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.ModuleWithSignature.3o Ocamlary.ModuleWithSignature.3o.gen)) + (diff Ocamlary.Dep7.argument-1-Arg.md Ocamlary.Dep7.argument-1-Arg.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary.ModuleWithSignatureAlias.3o - Ocamlary.ModuleWithSignatureAlias.3o.gen)) + Ocamlary.Dep7.argument-1-Arg.module-type-T.md + Ocamlary.Dep7.argument-1-Arg.module-type-T.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.One.3o Ocamlary.One.3o.gen)) + (diff + Ocamlary.Dep7.argument-1-Arg.X.md + Ocamlary.Dep7.argument-1-Arg.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Buffer.3o Ocamlary.Buffer.3o.gen)) + (diff Ocamlary.Dep7.M.md Ocamlary.Dep7.M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.CollectionModule.3o Ocamlary.CollectionModule.3o.gen)) + (diff Ocamlary.Dep8.md Ocamlary.Dep8.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.CollectionModule.InnerModuleA.3o - Ocamlary.CollectionModule.InnerModuleA.3o.gen)) + (diff Ocamlary.Dep8.module-type-T.md Ocamlary.Dep8.module-type-T.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o - Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.3o.gen)) + (diff Ocamlary.Dep9.md Ocamlary.Dep9.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Recollection.3o Ocamlary.Recollection.3o.gen)) + (diff Ocamlary.Dep9.argument-1-X.md Ocamlary.Dep9.argument-1-X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.Recollection.InnerModuleA.3o - Ocamlary.Recollection.InnerModuleA.3o.gen)) + (diff Ocamlary.module-type-Dep10.md Ocamlary.module-type-Dep10.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o - Ocamlary.Recollection.InnerModuleA.InnerModuleA'.3o.gen)) + (diff Ocamlary.Dep11.md Ocamlary.Dep11.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.FunctorTypeOf.3o Ocamlary.FunctorTypeOf.3o.gen)) + (diff Ocamlary.Dep11.module-type-S.md Ocamlary.Dep11.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.IncludedA.3o Ocamlary.IncludedA.3o.gen)) + (diff + Ocamlary.Dep11.module-type-S.c.md + Ocamlary.Dep11.module-type-S.c.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.ExtMod.3o Ocamlary.ExtMod.3o.gen)) + (diff Ocamlary.Dep12.md Ocamlary.Dep12.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.empty_class.3o Ocamlary.empty_class.3o.gen)) + (diff + Ocamlary.Dep12.argument-1-Arg.md + Ocamlary.Dep12.argument-1-Arg.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.one_method_class.3o Ocamlary.one_method_class.3o.gen)) + (diff Ocamlary.Dep13.md Ocamlary.Dep13.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.two_method_class.3o Ocamlary.two_method_class.3o.gen)) + (diff Ocamlary.Dep13.c.md Ocamlary.Dep13.c.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.param_class.3o Ocamlary.param_class.3o.gen)) + (diff Ocamlary.module-type-With1.md Ocamlary.module-type-With1.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep1.3o Ocamlary.Dep1.3o.gen)) + (diff Ocamlary.module-type-With1.M.md Ocamlary.module-type-With1.M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep1.X.3o Ocamlary.Dep1.X.3o.gen)) + (diff Ocamlary.With2.md Ocamlary.With2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep1.X.Y.3o Ocamlary.Dep1.X.Y.3o.gen)) + (diff Ocamlary.With2.module-type-S.md Ocamlary.With2.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep1.X.Y.c.3o Ocamlary.Dep1.X.Y.c.3o.gen)) + (diff Ocamlary.With3.md Ocamlary.With3.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep2.3o Ocamlary.Dep2.3o.gen)) + (diff Ocamlary.With3.N.md Ocamlary.With3.N.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep2.A.3o Ocamlary.Dep2.A.3o.gen)) + (diff Ocamlary.With4.md Ocamlary.With4.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep3.3o Ocamlary.Dep3.3o.gen)) + (diff Ocamlary.With4.N.md Ocamlary.With4.N.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep4.3o Ocamlary.Dep4.3o.gen)) + (diff Ocamlary.With5.md Ocamlary.With5.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep4.X.3o Ocamlary.Dep4.X.3o.gen)) + (diff Ocamlary.With5.module-type-S.md Ocamlary.With5.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep5.3o Ocamlary.Dep5.3o.gen)) + (diff Ocamlary.With5.N.md Ocamlary.With5.N.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep5.Z.3o Ocamlary.Dep5.Z.3o.gen)) + (diff Ocamlary.With6.md Ocamlary.With6.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep6.3o Ocamlary.Dep6.3o.gen)) + (diff Ocamlary.With6.module-type-T.md Ocamlary.With6.module-type-T.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep6.X.3o Ocamlary.Dep6.X.3o.gen)) + (diff + Ocamlary.With6.module-type-T.M.md + Ocamlary.With6.module-type-T.M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep6.X.Y.3o Ocamlary.Dep6.X.Y.3o.gen)) + (diff Ocamlary.With7.md Ocamlary.With7.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep7.3o Ocamlary.Dep7.3o.gen)) + (diff Ocamlary.With7.argument-1-X.md Ocamlary.With7.argument-1-X.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep7.M.3o Ocamlary.Dep7.M.3o.gen)) + (diff Ocamlary.module-type-With8.md Ocamlary.module-type-With8.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep8.3o Ocamlary.Dep8.3o.gen)) + (diff Ocamlary.module-type-With8.M.md Ocamlary.module-type-With8.M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep9.3o Ocamlary.Dep9.3o.gen)) + (diff + Ocamlary.module-type-With8.M.N.md + Ocamlary.module-type-With8.M.N.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep11.3o Ocamlary.Dep11.3o.gen)) + (diff Ocamlary.With9.md Ocamlary.With9.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep12.3o Ocamlary.Dep12.3o.gen)) + (diff Ocamlary.With9.module-type-S.md Ocamlary.With9.module-type-S.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep13.3o Ocamlary.Dep13.3o.gen)) + (diff Ocamlary.With10.md Ocamlary.With10.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Dep13.c.3o Ocamlary.Dep13.c.3o.gen)) + (diff + Ocamlary.With10.module-type-T.md + Ocamlary.With10.module-type-T.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With2.3o Ocamlary.With2.3o.gen)) + (diff + Ocamlary.With10.module-type-T.M.md + Ocamlary.With10.module-type-T.M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With3.3o Ocamlary.With3.3o.gen)) + (diff Ocamlary.module-type-With11.md Ocamlary.module-type-With11.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With3.N.3o Ocamlary.With3.N.3o.gen)) + (diff + Ocamlary.module-type-With11.N.md + Ocamlary.module-type-With11.N.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With4.3o Ocamlary.With4.3o.gen)) + (diff + Ocamlary.module-type-NestedInclude1.md + Ocamlary.module-type-NestedInclude1.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With4.N.3o Ocamlary.With4.N.3o.gen)) + (diff + Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md + Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With5.3o Ocamlary.With5.3o.gen)) + (diff + Ocamlary.module-type-NestedInclude2.md + Ocamlary.module-type-NestedInclude2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With5.N.3o Ocamlary.With5.N.3o.gen)) + (diff Ocamlary.DoubleInclude1.md Ocamlary.DoubleInclude1.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With6.3o Ocamlary.With6.3o.gen)) + (diff + Ocamlary.DoubleInclude1.DoubleInclude2.md + Ocamlary.DoubleInclude1.DoubleInclude2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With7.3o Ocamlary.With7.3o.gen)) + (diff Ocamlary.DoubleInclude3.md Ocamlary.DoubleInclude3.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With9.3o Ocamlary.With9.3o.gen)) + (diff + Ocamlary.DoubleInclude3.DoubleInclude2.md + Ocamlary.DoubleInclude3.DoubleInclude2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.With10.3o Ocamlary.With10.3o.gen)) + (diff Ocamlary.IncludeInclude1.md Ocamlary.IncludeInclude1.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.DoubleInclude1.3o Ocamlary.DoubleInclude1.3o.gen)) + (diff + Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md + Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary.DoubleInclude1.DoubleInclude2.3o - Ocamlary.DoubleInclude1.DoubleInclude2.3o.gen)) + Ocamlary.IncludeInclude1.IncludeInclude2_M.md + Ocamlary.IncludeInclude1.IncludeInclude2_M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.DoubleInclude3.3o Ocamlary.DoubleInclude3.3o.gen)) + (diff + Ocamlary.module-type-IncludeInclude2.md + Ocamlary.module-type-IncludeInclude2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.DoubleInclude3.DoubleInclude2.3o - Ocamlary.DoubleInclude3.DoubleInclude2.3o.gen)) + (diff Ocamlary.IncludeInclude2_M.md Ocamlary.IncludeInclude2_M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.IncludeInclude1.3o Ocamlary.IncludeInclude1.3o.gen)) + (diff Ocamlary.CanonicalTest.md Ocamlary.CanonicalTest.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.IncludeInclude1.IncludeInclude2_M.3o - Ocamlary.IncludeInclude1.IncludeInclude2_M.3o.gen)) + (diff Ocamlary.CanonicalTest.Base.md Ocamlary.CanonicalTest.Base.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.IncludeInclude2_M.3o Ocamlary.IncludeInclude2_M.3o.gen)) + (diff + Ocamlary.CanonicalTest.Base.List.md + Ocamlary.CanonicalTest.Base.List.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.CanonicalTest.3o Ocamlary.CanonicalTest.3o.gen)) + (diff + Ocamlary.CanonicalTest.Base_Tests.md + Ocamlary.CanonicalTest.Base_Tests.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.CanonicalTest.Base.3o Ocamlary.CanonicalTest.Base.3o.gen)) + (diff + Ocamlary.CanonicalTest.Base_Tests.C.md + Ocamlary.CanonicalTest.Base_Tests.C.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action (diff - Ocamlary.CanonicalTest.Base.List.3o - Ocamlary.CanonicalTest.Base.List.3o.gen)) + Ocamlary.CanonicalTest.List_modif.md + Ocamlary.CanonicalTest.List_modif.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.CanonicalTest.Base_Tests.3o - Ocamlary.CanonicalTest.Base_Tests.3o.gen)) + (diff Ocamlary.Aliases.md Ocamlary.Aliases.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.CanonicalTest.Base_Tests.C.3o - Ocamlary.CanonicalTest.Base_Tests.C.3o.gen)) + (diff Ocamlary.Aliases.Foo.md Ocamlary.Aliases.Foo.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff - Ocamlary.CanonicalTest.List_modif.3o - Ocamlary.CanonicalTest.List_modif.3o.gen)) + (diff Ocamlary.Aliases.Foo.A.md Ocamlary.Aliases.Foo.A.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.3o Ocamlary.Aliases.3o.gen)) + (diff Ocamlary.Aliases.Foo.B.md Ocamlary.Aliases.Foo.B.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Foo.3o Ocamlary.Aliases.Foo.3o.gen)) + (diff Ocamlary.Aliases.Foo.C.md Ocamlary.Aliases.Foo.C.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Foo.A.3o Ocamlary.Aliases.Foo.A.3o.gen)) + (diff Ocamlary.Aliases.Foo.D.md Ocamlary.Aliases.Foo.D.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Foo.B.3o Ocamlary.Aliases.Foo.B.3o.gen)) + (diff Ocamlary.Aliases.Foo.E.md Ocamlary.Aliases.Foo.E.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Foo.C.3o Ocamlary.Aliases.Foo.C.3o.gen)) + (diff Ocamlary.Aliases.Std.md Ocamlary.Aliases.Std.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Foo.D.3o Ocamlary.Aliases.Foo.D.3o.gen)) + (diff Ocamlary.Aliases.E.md Ocamlary.Aliases.E.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Foo.E.3o Ocamlary.Aliases.Foo.E.3o.gen)) + (diff Ocamlary.Aliases.P1.md Ocamlary.Aliases.P1.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.Std.3o Ocamlary.Aliases.Std.3o.gen)) + (diff Ocamlary.Aliases.P1.Y.md Ocamlary.Aliases.P1.Y.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.E.3o Ocamlary.Aliases.E.3o.gen)) + (diff Ocamlary.Aliases.P2.md Ocamlary.Aliases.P2.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.P1.3o Ocamlary.Aliases.P1.3o.gen)) + (diff Ocamlary.module-type-M.md Ocamlary.module-type-M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.P1.Y.3o Ocamlary.Aliases.P1.Y.3o.gen)) + (diff Ocamlary.M.md Ocamlary.M.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Aliases.P2.3o Ocamlary.Aliases.P2.3o.gen)) + (diff Ocamlary.Only_a_module.md Ocamlary.Only_a_module.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.M.3o Ocamlary.M.3o.gen)) + (diff Ocamlary.module-type-TypeExt.md Ocamlary.module-type-TypeExt.md.gen)) (enabled_if (>= %{ocaml_version} 4.07))) (rule (alias runtest) (action - (diff Ocamlary.Only_a_module.3o Ocamlary.Only_a_module.3o.gen)) + (diff + Ocamlary.module-type-TypeExtPruned.md + Ocamlary.module-type-TypeExtPruned.md.gen)) (enabled_if (>= %{ocaml_version} 4.07)))) (subdir - man + markdown (rule (action (with-outputs-to ocamlary.targets.gen - (run odoc man-targets -o . %{dep:../ocamlary.odocl}))) + (run odoc markdown-targets -o . %{dep:../ocamlary.odocl}))) (enabled_if (>= %{ocaml_version} 4.07))) (rule @@ -5638,6 +8468,104 @@ (enabled_if (>= %{ocaml_version} 4.09)))) +(subdir + markdown + (rule + (targets + Recent.md.gen + Recent.module-type-S.md.gen + Recent.module-type-S1.md.gen + Recent.module-type-S1.argument-1-_.md.gen + Recent.Z.md.gen + Recent.Z.Y.md.gen + Recent.Z.Y.X.md.gen + Recent.X.md.gen + Recent.module-type-PolyS.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../recent.odocl})) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.md Recent.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.module-type-S.md Recent.module-type-S.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.module-type-S1.md Recent.module-type-S1.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff + Recent.module-type-S1.argument-1-_.md + Recent.module-type-S1.argument-1-_.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.Z.md Recent.Z.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.Z.Y.md Recent.Z.Y.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.Z.Y.X.md Recent.Z.Y.X.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.X.md Recent.X.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent.module-type-PolyS.md Recent.module-type-PolyS.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + recent.targets.gen + (run odoc markdown-targets -o . %{dep:../recent.odocl}))) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff recent.targets recent.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.09)))) + (subdir html (rule @@ -5775,7 +8703,74 @@ (action (with-outputs-to recent_impl.targets.gen - (run odoc latex-targets -o . %{dep:../recent_impl.odocl}))) + (run odoc latex-targets -o . %{dep:../recent_impl.odocl}))) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff recent_impl.targets recent_impl.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.09)))) + +(subdir + man + (rule + (targets + Recent_impl.3o.gen + Recent_impl.Foo.3o.gen + Recent_impl.Foo.A.3o.gen + Recent_impl.Foo.B.3o.gen + Recent_impl.B.3o.gen) + (action + (run + odoc + man-generate + -o + . + --extra-suffix + gen + %{dep:../recent_impl.odocl})) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.3o Recent_impl.3o.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.Foo.3o Recent_impl.Foo.3o.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.Foo.A.3o Recent_impl.Foo.A.3o.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.Foo.B.3o Recent_impl.Foo.B.3o.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.B.3o Recent_impl.B.3o.gen)) + (enabled_if + (>= %{ocaml_version} 4.09)))) + +(subdir + man + (rule + (action + (with-outputs-to + recent_impl.targets.gen + (run odoc man-targets -o . %{dep:../recent_impl.odocl}))) (enabled_if (>= %{ocaml_version} 4.09))) (rule @@ -5786,18 +8781,23 @@ (>= %{ocaml_version} 4.09)))) (subdir - man + markdown (rule (targets - Recent_impl.3o.gen - Recent_impl.Foo.3o.gen - Recent_impl.Foo.A.3o.gen - Recent_impl.Foo.B.3o.gen - Recent_impl.B.3o.gen) + Recent_impl.md.gen + Recent_impl.Foo.md.gen + Recent_impl.Foo.A.md.gen + Recent_impl.Foo.B.md.gen + Recent_impl.B.md.gen + Recent_impl.module-type-S.md.gen + Recent_impl.module-type-S.F.md.gen + Recent_impl.module-type-S.F.argument-1-_.md.gen + Recent_impl.module-type-S.X.md.gen) (action (run odoc - man-generate + markdown-generate + --generate-links -o . --extra-suffix @@ -5808,41 +8808,67 @@ (rule (alias runtest) (action - (diff Recent_impl.3o Recent_impl.3o.gen)) + (diff Recent_impl.md Recent_impl.md.gen)) (enabled_if (>= %{ocaml_version} 4.09))) (rule (alias runtest) (action - (diff Recent_impl.Foo.3o Recent_impl.Foo.3o.gen)) + (diff Recent_impl.Foo.md Recent_impl.Foo.md.gen)) (enabled_if (>= %{ocaml_version} 4.09))) (rule (alias runtest) (action - (diff Recent_impl.Foo.A.3o Recent_impl.Foo.A.3o.gen)) + (diff Recent_impl.Foo.A.md Recent_impl.Foo.A.md.gen)) (enabled_if (>= %{ocaml_version} 4.09))) (rule (alias runtest) (action - (diff Recent_impl.Foo.B.3o Recent_impl.Foo.B.3o.gen)) + (diff Recent_impl.Foo.B.md Recent_impl.Foo.B.md.gen)) (enabled_if (>= %{ocaml_version} 4.09))) (rule (alias runtest) (action - (diff Recent_impl.B.3o Recent_impl.B.3o.gen)) + (diff Recent_impl.B.md Recent_impl.B.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.module-type-S.md Recent_impl.module-type-S.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.module-type-S.F.md Recent_impl.module-type-S.F.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff + Recent_impl.module-type-S.F.argument-1-_.md + Recent_impl.module-type-S.F.argument-1-_.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.09))) + (rule + (alias runtest) + (action + (diff Recent_impl.module-type-S.X.md Recent_impl.module-type-S.X.md.gen)) (enabled_if (>= %{ocaml_version} 4.09)))) (subdir - man + markdown (rule (action (with-outputs-to recent_impl.targets.gen - (run odoc man-targets -o . %{dep:../recent_impl.odocl}))) + (run odoc markdown-targets -o . %{dep:../recent_impl.odocl}))) (enabled_if (>= %{ocaml_version} 4.09))) (rule @@ -5930,6 +8956,37 @@ (action (diff section.targets section.targets.gen)))) +(subdir + markdown + (rule + (targets Section.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../section.odocl}))) + (rule + (alias runtest) + (action + (diff Section.md Section.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + section.targets.gen + (run odoc markdown-targets -o . %{dep:../section.odocl})))) + (rule + (alias runtest) + (action + (diff section.targets section.targets.gen)))) + (subdir html (rule @@ -6016,6 +9073,41 @@ (action (diff stop.targets stop.targets.gen)))) +(subdir + markdown + (rule + (targets Stop.md.gen Stop.N.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../stop.odocl}))) + (rule + (alias runtest) + (action + (diff Stop.md Stop.md.gen))) + (rule + (alias runtest) + (action + (diff Stop.N.md Stop.N.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + stop.targets.gen + (run odoc markdown-targets -o . %{dep:../stop.odocl})))) + (rule + (alias runtest) + (action + (diff stop.targets stop.targets.gen)))) + (subdir html (rule @@ -6144,6 +9236,51 @@ (enabled_if (>= %{ocaml_version} 4.04)))) +(subdir + markdown + (rule + (targets Stop_dead_link_doc.md.gen Stop_dead_link_doc.Foo.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../stop_dead_link_doc.odocl})) + (enabled_if + (>= %{ocaml_version} 4.04))) + (rule + (alias runtest) + (action + (diff Stop_dead_link_doc.md Stop_dead_link_doc.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.04))) + (rule + (alias runtest) + (action + (diff Stop_dead_link_doc.Foo.md Stop_dead_link_doc.Foo.md.gen)) + (enabled_if + (>= %{ocaml_version} 4.04)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + stop_dead_link_doc.targets.gen + (run odoc markdown-targets -o . %{dep:../stop_dead_link_doc.odocl}))) + (enabled_if + (>= %{ocaml_version} 4.04))) + (rule + (alias runtest) + (action + (diff stop_dead_link_doc.targets stop_dead_link_doc.targets.gen)) + (enabled_if + (>= %{ocaml_version} 4.04)))) + (subdir html (rule @@ -6412,6 +9549,131 @@ (action (diff toplevel_comments.targets toplevel_comments.targets.gen)))) +(subdir + markdown + (rule + (targets + Toplevel_comments.md.gen + Toplevel_comments.module-type-T.md.gen + Toplevel_comments.Include_inline.md.gen + Toplevel_comments.Include_inline'.md.gen + Toplevel_comments.module-type-Include_inline_T.md.gen + Toplevel_comments.module-type-Include_inline_T'.md.gen + Toplevel_comments.M.md.gen + Toplevel_comments.M'.md.gen + Toplevel_comments.M''.md.gen + Toplevel_comments.Alias.md.gen + Toplevel_comments.c1.md.gen + Toplevel_comments.class-type-ct.md.gen + Toplevel_comments.c2.md.gen + Toplevel_comments.Ref_in_synopsis.md.gen + Toplevel_comments.Comments_on_open.md.gen + Toplevel_comments.Comments_on_open.M.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../toplevel_comments.odocl}))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.md Toplevel_comments.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.module-type-T.md + Toplevel_comments.module-type-T.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.Include_inline.md + Toplevel_comments.Include_inline.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.Include_inline'.md + Toplevel_comments.Include_inline'.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.module-type-Include_inline_T.md + Toplevel_comments.module-type-Include_inline_T.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.module-type-Include_inline_T'.md + Toplevel_comments.module-type-Include_inline_T'.md.gen))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.M.md Toplevel_comments.M.md.gen))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.M'.md Toplevel_comments.M'.md.gen))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.M''.md Toplevel_comments.M''.md.gen))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.Alias.md Toplevel_comments.Alias.md.gen))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.c1.md Toplevel_comments.c1.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.class-type-ct.md + Toplevel_comments.class-type-ct.md.gen))) + (rule + (alias runtest) + (action + (diff Toplevel_comments.c2.md Toplevel_comments.c2.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.Ref_in_synopsis.md + Toplevel_comments.Ref_in_synopsis.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.Comments_on_open.md + Toplevel_comments.Comments_on_open.md.gen))) + (rule + (alias runtest) + (action + (diff + Toplevel_comments.Comments_on_open.M.md + Toplevel_comments.Comments_on_open.M.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + toplevel_comments.targets.gen + (run odoc markdown-targets -o . %{dep:../toplevel_comments.odocl})))) + (rule + (alias runtest) + (action + (diff toplevel_comments.targets toplevel_comments.targets.gen)))) + (subdir html (rule @@ -6494,6 +9756,41 @@ (action (diff type.targets type.targets.gen)))) +(subdir + markdown + (rule + (targets Type.md.gen Type.module-type-X.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../type.odocl}))) + (rule + (alias runtest) + (action + (diff Type.md Type.md.gen))) + (rule + (alias runtest) + (action + (diff Type.module-type-X.md Type.module-type-X.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + type.targets.gen + (run odoc markdown-targets -o . %{dep:../type.odocl})))) + (rule + (alias runtest) + (action + (diff type.targets type.targets.gen)))) + (subdir html (rule @@ -6571,3 +9868,34 @@ (alias runtest) (action (diff val.targets val.targets.gen)))) + +(subdir + markdown + (rule + (targets Val.md.gen) + (action + (run + odoc + markdown-generate + --generate-links + -o + . + --extra-suffix + gen + %{dep:../val.odocl}))) + (rule + (alias runtest) + (action + (diff Val.md Val.md.gen)))) + +(subdir + markdown + (rule + (action + (with-outputs-to + val.targets.gen + (run odoc markdown-targets -o . %{dep:../val.odocl})))) + (rule + (alias runtest) + (action + (diff val.targets val.targets.gen)))) diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md new file mode 100644 index 0000000000..b650d69e61 --- /dev/null +++ b/test/generators/markdown/Alias.X.md @@ -0,0 +1,14 @@ +Alias + +X + +Module Alias.X + + + +###### type t = + +> int + + +Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' \ No newline at end of file diff --git a/test/generators/markdown/Alias.md b/test/generators/markdown/Alias.md new file mode 100644 index 0000000000..eb4448c9cb --- /dev/null +++ b/test/generators/markdown/Alias.md @@ -0,0 +1,7 @@ +Alias + +Module Alias + + + +###### module [X](Alias.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md new file mode 100644 index 0000000000..7a794902b5 --- /dev/null +++ b/test/generators/markdown/Bugs.md @@ -0,0 +1,19 @@ +Bugs + +Module Bugs + + + +###### type 'a opt = + +> 'a option + + + + +###### val foo : + +> ? bar : 'a -> unit -> unit + + +Triggers an assertion failure when \ No newline at end of file diff --git a/test/generators/markdown/Bugs_post_406.class-type-let_open.md b/test/generators/markdown/Bugs_post_406.class-type-let_open.md new file mode 100644 index 0000000000..6b68604881 --- /dev/null +++ b/test/generators/markdown/Bugs_post_406.class-type-let_open.md @@ -0,0 +1,5 @@ +Bugs_post_406 + +let_open + +Class type Bugs_post_406.let_open \ No newline at end of file diff --git a/test/generators/markdown/Bugs_post_406.let_open'.md b/test/generators/markdown/Bugs_post_406.let_open'.md new file mode 100644 index 0000000000..62c319d14c --- /dev/null +++ b/test/generators/markdown/Bugs_post_406.let_open'.md @@ -0,0 +1,5 @@ +Bugs_post_406 + +let_open' + +Class Bugs_post_406.let_open' \ No newline at end of file diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md new file mode 100644 index 0000000000..9ab4d4c0e6 --- /dev/null +++ b/test/generators/markdown/Bugs_post_406.md @@ -0,0 +1,13 @@ +Bugs_post_406 + +Module Bugs_post_406 + +Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 + + + +###### class type [let_open](Bugs_post_406.class-type-let_open.md) + + + +###### class [let_open'](Bugs_post_406.let_open'.md) \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-empty.md b/test/generators/markdown/Class.class-type-empty.md new file mode 100644 index 0000000000..06e54aec60 --- /dev/null +++ b/test/generators/markdown/Class.class-type-empty.md @@ -0,0 +1,5 @@ +Class + +empty + +Class type Class.empty \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-empty_virtual.md b/test/generators/markdown/Class.class-type-empty_virtual.md new file mode 100644 index 0000000000..546a1971da --- /dev/null +++ b/test/generators/markdown/Class.class-type-empty_virtual.md @@ -0,0 +1,5 @@ +Class + +empty_virtual + +Class type Class.empty_virtual \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-mutually.md b/test/generators/markdown/Class.class-type-mutually.md new file mode 100644 index 0000000000..6b210587b8 --- /dev/null +++ b/test/generators/markdown/Class.class-type-mutually.md @@ -0,0 +1,5 @@ +Class + +mutually + +Class type Class.mutually \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-polymorphic.md b/test/generators/markdown/Class.class-type-polymorphic.md new file mode 100644 index 0000000000..5848792d07 --- /dev/null +++ b/test/generators/markdown/Class.class-type-polymorphic.md @@ -0,0 +1,5 @@ +Class + +polymorphic + +Class type Class.polymorphic \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-recursive.md b/test/generators/markdown/Class.class-type-recursive.md new file mode 100644 index 0000000000..ddb5752369 --- /dev/null +++ b/test/generators/markdown/Class.class-type-recursive.md @@ -0,0 +1,5 @@ +Class + +recursive + +Class type Class.recursive \ No newline at end of file diff --git a/test/generators/markdown/Class.empty_virtual'.md b/test/generators/markdown/Class.empty_virtual'.md new file mode 100644 index 0000000000..9c3d15bced --- /dev/null +++ b/test/generators/markdown/Class.empty_virtual'.md @@ -0,0 +1,5 @@ +Class + +empty_virtual' + +Class Class.empty_virtual' \ No newline at end of file diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md new file mode 100644 index 0000000000..bcabfbd22c --- /dev/null +++ b/test/generators/markdown/Class.md @@ -0,0 +1,39 @@ +Class + +Module Class + + + +###### class type [empty](Class.class-type-empty.md) + + + +###### class type [mutually](Class.class-type-mutually.md) + + + +###### class type [recursive](Class.class-type-recursive.md) + + + +###### class [mutually'](Class.mutually'.md) + + + +###### class [recursive'](Class.recursive'.md) + + + +###### class type virtual [empty_virtual](Class.class-type-empty_virtual.md) + + + +###### class virtual [empty_virtual'](Class.empty_virtual'.md) + + + +###### class type 'a [polymorphic](Class.class-type-polymorphic.md) + + + +###### class 'a [polymorphic'](Class.polymorphic'.md) \ No newline at end of file diff --git a/test/generators/markdown/Class.mutually'.md b/test/generators/markdown/Class.mutually'.md new file mode 100644 index 0000000000..29ba8fab85 --- /dev/null +++ b/test/generators/markdown/Class.mutually'.md @@ -0,0 +1,5 @@ +Class + +mutually' + +Class Class.mutually' \ No newline at end of file diff --git a/test/generators/markdown/Class.polymorphic'.md b/test/generators/markdown/Class.polymorphic'.md new file mode 100644 index 0000000000..dbc1c394d5 --- /dev/null +++ b/test/generators/markdown/Class.polymorphic'.md @@ -0,0 +1,5 @@ +Class + +polymorphic' + +Class Class.polymorphic' \ No newline at end of file diff --git a/test/generators/markdown/Class.recursive'.md b/test/generators/markdown/Class.recursive'.md new file mode 100644 index 0000000000..117d8e5984 --- /dev/null +++ b/test/generators/markdown/Class.recursive'.md @@ -0,0 +1,5 @@ +Class + +recursive' + +Class Class.recursive' \ No newline at end of file diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md new file mode 100644 index 0000000000..0195935424 --- /dev/null +++ b/test/generators/markdown/External.md @@ -0,0 +1,12 @@ +External + +Module External + + + +###### val foo : + +> unit -> unit + + +Foo \ No newline at end of file diff --git a/test/generators/markdown/Functor.F1.argument-1-Arg.md b/test/generators/markdown/Functor.F1.argument-1-Arg.md new file mode 100644 index 0000000000..8133c65efd --- /dev/null +++ b/test/generators/markdown/Functor.F1.argument-1-Arg.md @@ -0,0 +1,11 @@ +Functor + +F1 + +1-Arg + +Parameter F1.1-Arg + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.F1.md b/test/generators/markdown/Functor.F1.md new file mode 100644 index 0000000000..78297ce6ed --- /dev/null +++ b/test/generators/markdown/Functor.F1.md @@ -0,0 +1,17 @@ +Functor + +F1 + +Module Functor.F1 + +# Parameters + + + +###### module [Arg](Functor.F1.argument-1-Arg.md) + +# Signature + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.F2.argument-1-Arg.md b/test/generators/markdown/Functor.F2.argument-1-Arg.md new file mode 100644 index 0000000000..895c3fdcbb --- /dev/null +++ b/test/generators/markdown/Functor.F2.argument-1-Arg.md @@ -0,0 +1,11 @@ +Functor + +F2 + +1-Arg + +Parameter F2.1-Arg + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.F2.md b/test/generators/markdown/Functor.F2.md new file mode 100644 index 0000000000..af71f9c680 --- /dev/null +++ b/test/generators/markdown/Functor.F2.md @@ -0,0 +1,19 @@ +Functor + +F2 + +Module Functor.F2 + +# Parameters + + + +###### module [Arg](Functor.F2.argument-1-Arg.md) + +# Signature + + + +###### type t = + +> [Arg.t](Functor.F2.argument-1-Arg.md#type-t) diff --git a/test/generators/markdown/Functor.F3.argument-1-Arg.md b/test/generators/markdown/Functor.F3.argument-1-Arg.md new file mode 100644 index 0000000000..a993e0b519 --- /dev/null +++ b/test/generators/markdown/Functor.F3.argument-1-Arg.md @@ -0,0 +1,11 @@ +Functor + +F3 + +1-Arg + +Parameter F3.1-Arg + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.F3.md b/test/generators/markdown/Functor.F3.md new file mode 100644 index 0000000000..83123a8670 --- /dev/null +++ b/test/generators/markdown/Functor.F3.md @@ -0,0 +1,19 @@ +Functor + +F3 + +Module Functor.F3 + +# Parameters + + + +###### module [Arg](Functor.F3.argument-1-Arg.md) + +# Signature + + + +###### type t = + +> [Arg.t](Functor.F3.argument-1-Arg.md#type-t) diff --git a/test/generators/markdown/Functor.F4.argument-1-Arg.md b/test/generators/markdown/Functor.F4.argument-1-Arg.md new file mode 100644 index 0000000000..69b55399ec --- /dev/null +++ b/test/generators/markdown/Functor.F4.argument-1-Arg.md @@ -0,0 +1,11 @@ +Functor + +F4 + +1-Arg + +Parameter F4.1-Arg + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.F4.md b/test/generators/markdown/Functor.F4.md new file mode 100644 index 0000000000..e72e2c0e1a --- /dev/null +++ b/test/generators/markdown/Functor.F4.md @@ -0,0 +1,17 @@ +Functor + +F4 + +Module Functor.F4 + +# Parameters + + + +###### module [Arg](Functor.F4.argument-1-Arg.md) + +# Signature + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.F5.md b/test/generators/markdown/Functor.F5.md new file mode 100644 index 0000000000..f1b6403f87 --- /dev/null +++ b/test/generators/markdown/Functor.F5.md @@ -0,0 +1,13 @@ +Functor + +F5 + +Module Functor.F5 + +# Parameters + +# Signature + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.md b/test/generators/markdown/Functor.md new file mode 100644 index 0000000000..bb16940272 --- /dev/null +++ b/test/generators/markdown/Functor.md @@ -0,0 +1,31 @@ +Functor + +Module Functor + + + +###### module type [S](Functor.module-type-S.md) + + + +###### module type [S1](Functor.module-type-S1.md) + + + +###### module [F1](Functor.F1.md) + + + +###### module [F2](Functor.F2.md) + + + +###### module [F3](Functor.F3.md) + + + +###### module [F4](Functor.F4.md) + + + +###### module [F5](Functor.F5.md) \ No newline at end of file diff --git a/test/generators/markdown/Functor.module-type-S.md b/test/generators/markdown/Functor.module-type-S.md new file mode 100644 index 0000000000..cb4e417959 --- /dev/null +++ b/test/generators/markdown/Functor.module-type-S.md @@ -0,0 +1,9 @@ +Functor + +S + +Module type Functor.S + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.module-type-S1.argument-1-_.md b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md new file mode 100644 index 0000000000..8c5c46f3b0 --- /dev/null +++ b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md @@ -0,0 +1,11 @@ +Functor + +S1 + +1-_ + +Parameter S1.1-_ + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor.module-type-S1.md b/test/generators/markdown/Functor.module-type-S1.md new file mode 100644 index 0000000000..c31ae63a25 --- /dev/null +++ b/test/generators/markdown/Functor.module-type-S1.md @@ -0,0 +1,17 @@ +Functor + +S1 + +Module type Functor.S1 + +# Parameters + + + +###### module [_](Functor.module-type-S1.argument-1-_.md) + +# Signature + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor2.X.argument-1-Y.md b/test/generators/markdown/Functor2.X.argument-1-Y.md new file mode 100644 index 0000000000..13f784fce9 --- /dev/null +++ b/test/generators/markdown/Functor2.X.argument-1-Y.md @@ -0,0 +1,11 @@ +Functor2 + +X + +1-Y + +Parameter X.1-Y + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor2.X.argument-2-Z.md b/test/generators/markdown/Functor2.X.argument-2-Z.md new file mode 100644 index 0000000000..17dbb5f697 --- /dev/null +++ b/test/generators/markdown/Functor2.X.argument-2-Z.md @@ -0,0 +1,11 @@ +Functor2 + +X + +2-Z + +Parameter X.2-Z + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor2.X.md b/test/generators/markdown/Functor2.X.md new file mode 100644 index 0000000000..ffc40681d3 --- /dev/null +++ b/test/generators/markdown/Functor2.X.md @@ -0,0 +1,37 @@ +Functor2 + +X + +Module Functor2.X + +# Parameters + + + +###### module [Y](Functor2.X.argument-1-Y.md) + + + +###### module [Z](Functor2.X.argument-2-Z.md) + +# Signature + + + +###### type y_t = + +> [Y.t](Functor2.X.argument-1-Y.md#type-t) + + + + +###### type z_t = + +> [Z.t](Functor2.X.argument-2-Z.md#type-t) + + + + +###### type x_t = + +> [y_t](#type-y_t) diff --git a/test/generators/markdown/Functor2.md b/test/generators/markdown/Functor2.md new file mode 100644 index 0000000000..184809e944 --- /dev/null +++ b/test/generators/markdown/Functor2.md @@ -0,0 +1,15 @@ +Functor2 + +Module Functor2 + + + +###### module type [S](Functor2.module-type-S.md) + + + +###### module [X](Functor2.X.md) + + + +###### module type [XF](Functor2.module-type-XF.md) \ No newline at end of file diff --git a/test/generators/markdown/Functor2.module-type-S.md b/test/generators/markdown/Functor2.module-type-S.md new file mode 100644 index 0000000000..2021592466 --- /dev/null +++ b/test/generators/markdown/Functor2.module-type-S.md @@ -0,0 +1,9 @@ +Functor2 + +S + +Module type Functor2.S + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md b/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md new file mode 100644 index 0000000000..6ff792ac2b --- /dev/null +++ b/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md @@ -0,0 +1,11 @@ +Functor2 + +XF + +1-Y + +Parameter XF.1-Y + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md b/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md new file mode 100644 index 0000000000..35ecf8495f --- /dev/null +++ b/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md @@ -0,0 +1,11 @@ +Functor2 + +XF + +2-Z + +Parameter XF.2-Z + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Functor2.module-type-XF.md b/test/generators/markdown/Functor2.module-type-XF.md new file mode 100644 index 0000000000..42f1542955 --- /dev/null +++ b/test/generators/markdown/Functor2.module-type-XF.md @@ -0,0 +1,37 @@ +Functor2 + +XF + +Module type Functor2.XF + +# Parameters + + + +###### module [Y](Functor2.module-type-XF.argument-1-Y.md) + + + +###### module [Z](Functor2.module-type-XF.argument-2-Z.md) + +# Signature + + + +###### type y_t = + +> [Y.t](Functor2.module-type-XF.argument-1-Y.md#type-t) + + + + +###### type z_t = + +> [Z.t](Functor2.module-type-XF.argument-2-Z.md#type-t) + + + + +###### type x_t = + +> [y_t](#type-y_t) diff --git a/test/generators/markdown/Include.md b/test/generators/markdown/Include.md new file mode 100644 index 0000000000..2a3617f0a8 --- /dev/null +++ b/test/generators/markdown/Include.md @@ -0,0 +1,47 @@ +Include + +Module Include + + + +###### module type [Not_inlined](Include.module-type-Not_inlined.md) + + + +###### type t + + + +###### module type [Inlined](Include.module-type-Inlined.md) + + + +###### type u + + + +###### module type [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) + +include [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) + + + +###### module type [Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) + + + +###### type w + + + +###### module type [Inherent_Module](Include.module-type-Inherent_Module.md) + + + +###### module type [Dorminant_Module](Include.module-type-Dorminant_Module.md) + + + +###### val a : + +> [u](#type-u) diff --git a/test/generators/markdown/Include.module-type-Dorminant_Module.md b/test/generators/markdown/Include.module-type-Dorminant_Module.md new file mode 100644 index 0000000000..0a1686d4ec --- /dev/null +++ b/test/generators/markdown/Include.module-type-Dorminant_Module.md @@ -0,0 +1,11 @@ +Include + +Dorminant_Module + +Module type Include.Dorminant_Module + + + +###### val a : + +> [u](Include.md#type-u) diff --git a/test/generators/markdown/Include.module-type-Inherent_Module.md b/test/generators/markdown/Include.module-type-Inherent_Module.md new file mode 100644 index 0000000000..c2ca674158 --- /dev/null +++ b/test/generators/markdown/Include.module-type-Inherent_Module.md @@ -0,0 +1,11 @@ +Include + +Inherent_Module + +Module type Include.Inherent_Module + + + +###### val a : + +> [t](Include.md#type-t) diff --git a/test/generators/markdown/Include.module-type-Inlined.md b/test/generators/markdown/Include.module-type-Inlined.md new file mode 100644 index 0000000000..420f9567a5 --- /dev/null +++ b/test/generators/markdown/Include.module-type-Inlined.md @@ -0,0 +1,9 @@ +Include + +Inlined + +Module type Include.Inlined + + + +###### type u \ No newline at end of file diff --git a/test/generators/markdown/Include.module-type-Not_inlined.md b/test/generators/markdown/Include.module-type-Not_inlined.md new file mode 100644 index 0000000000..391c80c31e --- /dev/null +++ b/test/generators/markdown/Include.module-type-Not_inlined.md @@ -0,0 +1,9 @@ +Include + +Not_inlined + +Module type Include.Not_inlined + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md b/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md new file mode 100644 index 0000000000..1505118984 --- /dev/null +++ b/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md @@ -0,0 +1,9 @@ +Include + +Not_inlined_and_closed + +Module type Include.Not_inlined_and_closed + + + +###### type v \ No newline at end of file diff --git a/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md b/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md new file mode 100644 index 0000000000..d1f94edc0b --- /dev/null +++ b/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md @@ -0,0 +1,9 @@ +Include + +Not_inlined_and_opened + +Module type Include.Not_inlined_and_opened + + + +###### type w \ No newline at end of file diff --git a/test/generators/markdown/Include2.X.md b/test/generators/markdown/Include2.X.md new file mode 100644 index 0000000000..5c413acd96 --- /dev/null +++ b/test/generators/markdown/Include2.X.md @@ -0,0 +1,13 @@ +Include2 + +X + +Module Include2.X + +Comment about X that should not appear when including X below. + + + +###### type t = + +> int diff --git a/test/generators/markdown/Include2.Y.md b/test/generators/markdown/Include2.Y.md new file mode 100644 index 0000000000..34b679e4a1 --- /dev/null +++ b/test/generators/markdown/Include2.Y.md @@ -0,0 +1,11 @@ +Include2 + +Y + +Module Include2.Y + +Top-comment of Y. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Include2.Y_include_doc.md b/test/generators/markdown/Include2.Y_include_doc.md new file mode 100644 index 0000000000..b2db9e7887 --- /dev/null +++ b/test/generators/markdown/Include2.Y_include_doc.md @@ -0,0 +1,11 @@ +Include2 + +Y_include_doc + +Module Include2.Y_include_doc + + + +###### type t = + +> [Y.t](Include2.Y.md#type-t) diff --git a/test/generators/markdown/Include2.Y_include_synopsis.md b/test/generators/markdown/Include2.Y_include_synopsis.md new file mode 100644 index 0000000000..ffb495f05e --- /dev/null +++ b/test/generators/markdown/Include2.Y_include_synopsis.md @@ -0,0 +1,13 @@ +Include2 + +Y_include_synopsis + +Module Include2.Y_include_synopsis + +The include Y below should have the synopsis from Y 's top-comment attached to it. + + + +###### type t = + +> [Y.t](Include2.Y.md#type-t) diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md new file mode 100644 index 0000000000..f8c21355a6 --- /dev/null +++ b/test/generators/markdown/Include2.md @@ -0,0 +1,34 @@ +Include2 + +Module Include2 + + + +###### module [X](Include2.X.md) + +Comment about X that should not appear when including X below. + +Comment about X that should not appear when including X below. + + + +###### type t = + +> int + + + + +###### module [Y](Include2.Y.md) + +Top-comment of Y. + + + +###### module [Y_include_synopsis](Include2.Y_include_synopsis.md) + +The `include Y` + + + +###### module [Y_include_doc](Include2.Y_include_doc.md) \ No newline at end of file diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md new file mode 100644 index 0000000000..fa9c50a56f --- /dev/null +++ b/test/generators/markdown/Include_sections.md @@ -0,0 +1,94 @@ +Include_sections + +Module Include_sections + + + +###### module type [Something](Include_sections.module-type-Something.md) + +A module type. + +Let's include [Something](Include_sections.module-type-Something.md) once + +# Something 1 + +foo + +## Something 2 + +--- + +# Something 1-bis + +Some text. + +# Second include + +Let's include [Something](Include_sections.module-type-Something.md) a second time: the heading level should be shift here. + +# Something 1 + +foo + +## Something 2 + +--- + +# Something 1-bis + +Some text. + +## Third include + +--- + +Shifted some more. + +# Something 1 + +foo + +## Something 2 + +--- + +# Something 1-bis + +Some text. + +And let's include it again, but without inlining it this time: the ToC shouldn't grow. + + + +###### val something : + +> unit + + +# Something 1 + +foo + + + +###### val foo : + +> unit + + +## Something 2 + +--- + + + +###### val bar : + +> unit + + +foo bar + +# Something 1-bis + +Some text. \ No newline at end of file diff --git a/test/generators/markdown/Include_sections.module-type-Something.md b/test/generators/markdown/Include_sections.module-type-Something.md new file mode 100644 index 0000000000..9e05d40fbf --- /dev/null +++ b/test/generators/markdown/Include_sections.module-type-Something.md @@ -0,0 +1,42 @@ +Include_sections + +Something + +Module type Include_sections.Something + +A module type. + + + +###### val something : + +> unit + + +# Something 1 + +foo + + + +###### val foo : + +> unit + + +## Something 2 + +--- + + + +###### val bar : + +> unit + + +foo bar + +# Something 1-bis + +Some text. \ No newline at end of file diff --git a/test/generators/markdown/Interlude.md b/test/generators/markdown/Interlude.md new file mode 100644 index 0000000000..c583931174 --- /dev/null +++ b/test/generators/markdown/Interlude.md @@ -0,0 +1,54 @@ +Interlude + +Module Interlude + +This is the comment associated to the module. + +Some separate stray text at the top of the module. + + + +###### val foo : + +> unit + + +Foo. + +Some stray text that is not associated with any signature item. + +It has multiple paragraphs. + +A separate block of stray text, adjacent to the preceding one. + + + +###### val bar : + +> unit + + +Bar. + + + +###### val multiple : + +> unit + + + + +###### val signature : + +> unit + + + + +###### val items : + +> unit + + +Stray text at the bottom of the module. \ No newline at end of file diff --git a/test/generators/markdown/Labels.A.md b/test/generators/markdown/Labels.A.md new file mode 100644 index 0000000000..18762d29e9 --- /dev/null +++ b/test/generators/markdown/Labels.A.md @@ -0,0 +1,7 @@ +Labels + +A + +Module Labels.A + +# Attached to module \ No newline at end of file diff --git a/test/generators/markdown/Labels.c.md b/test/generators/markdown/Labels.c.md new file mode 100644 index 0000000000..8993888182 --- /dev/null +++ b/test/generators/markdown/Labels.c.md @@ -0,0 +1,7 @@ +Labels + +c + +Class Labels.c + +# Attached to class \ No newline at end of file diff --git a/test/generators/markdown/Labels.class-type-cs.md b/test/generators/markdown/Labels.class-type-cs.md new file mode 100644 index 0000000000..66f0675cf4 --- /dev/null +++ b/test/generators/markdown/Labels.class-type-cs.md @@ -0,0 +1,7 @@ +Labels + +cs + +Class type Labels.cs + +# Attached to class type \ No newline at end of file diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md new file mode 100644 index 0000000000..7d19dc0e1e --- /dev/null +++ b/test/generators/markdown/Labels.md @@ -0,0 +1,140 @@ +Labels + +Module Labels + +# Attached to unit + +# Attached to nothing + + + +###### module [A](Labels.A.md) + + + +###### type t + +Attached to type + + + +###### val f : + +> [t](#type-t) + + +Attached to value + + + +###### val e : + +> unit -> [t](#type-t) + + +Attached to external + + + +###### module type [S](Labels.module-type-S.md) + + + +###### class [c](Labels.c.md) + + + +###### class type [cs](Labels.class-type-cs.md) + + + +###### exception E + +Attached to exception + + + +###### type x = + +> .. + + + + +###### type [x](#type-x) += + + + +######    | X + +Attached to extension + + + +###### module S := + +> [A](Labels.A.md) + + +Attached to module subst + + + +###### type s := + +> [t](#type-t) + + +Attached to type subst + + + +###### type u = + + + +######    | A' + +Attached to constructor + + + +###### type v = { + + + +######    f : [t](#type-t) ; + +Attached to field + +} + +Testing that labels can be referenced + +- [Attached to unit](#L1) + +- [Attached to nothing](#L2) + +- [Attached to module](#L3) + +- [Attached to type](#L4) + +- [Attached to value](#L5) + +- [Attached to module type](#L6) + +- [Attached to class](#L7) + +- [Attached to class type](#L8) + +- [Attached to exception](#L9) + +- [Attached to extension](#L10) + +- [Attached to module subst](#L11) + +- [Attached to type subst](#L12) + +- [Attached to constructor](#L13) + +- [Attached to field](#L14) \ No newline at end of file diff --git a/test/generators/markdown/Labels.module-type-S.md b/test/generators/markdown/Labels.module-type-S.md new file mode 100644 index 0000000000..d528b3a0f2 --- /dev/null +++ b/test/generators/markdown/Labels.module-type-S.md @@ -0,0 +1,7 @@ +Labels + +S + +Module type Labels.S + +# Attached to module type \ No newline at end of file diff --git a/test/generators/markdown/Markup.X.md b/test/generators/markdown/Markup.X.md new file mode 100644 index 0000000000..e1610e9022 --- /dev/null +++ b/test/generators/markdown/Markup.X.md @@ -0,0 +1,5 @@ +Markup + +X + +Module Markup.X \ No newline at end of file diff --git a/test/generators/markdown/Markup.Y.md b/test/generators/markdown/Markup.Y.md new file mode 100644 index 0000000000..7671336ac5 --- /dev/null +++ b/test/generators/markdown/Markup.Y.md @@ -0,0 +1,5 @@ +Markup + +Y + +Module Markup.Y \ No newline at end of file diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md new file mode 100644 index 0000000000..50fd8bd180 --- /dev/null +++ b/test/generators/markdown/Markup.md @@ -0,0 +1,183 @@ +Markup + +Module Markup + +Here, we test the rendering of comment markup. + +# Sections + +Let's get these done first, because sections will be used to break up the rest of this test. + +Besides the section heading above, there are also + +## Subsection headings + +--- + +and + +### Sub-subsection headings + +--- + +but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. + +### Anchors + +--- + +Sections can have attached [Anchors](#anchors) , and it is possible to [link](#anchors) to them. Links to section headers should not be set in source code style. + +#### Paragraph + +--- + +Individual paragraphs can have a heading. + +##### Subparagraph + +--- + +Parts of a longer paragraph that can be considered alone can also have headings. + +# Styling + +This paragraph has some styled elements: **bold** and _italic_ , **_bold italic_** , _emphasis_ , __emphasis_ within emphasis_ , **_bold italic_** , super script , sub script . The line spacing should be enough for superscripts and subscripts not to look odd. + +Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ emphasis_ is rendered in italics._ _It also work the same in [links in italics with _emphasis _in_ emphasis_ .](#)_ + +code is a different kind of markup that doesn't allow nested markup. + +It's possible for two markup elements to appear **next** _to_ each other and have a space, and appear **next** _to_ each other with no space. It doesn't matter **how** _much_ space it was in the source: in this sentence, it was two space characters. And in this one, there is **a** _newline_ . + +This is also true between _non-_ code markup _and_ code . + +Code can appear **inside other markup** . Its display shouldn't be affected. + +# Links and references + +This is a [link](#) . It sends you to the top of this page. Links can have markup inside them: [**bold**](#) , [_italics_](#) , [_emphasis_](#) , [super script](#) , [sub script](#) , and [code](#) . Links can also be nested _[inside](#)_ markup. Links cannot be nested inside each other. This link has no replacement text: [#](#) . The text is filled in by odoc. This is a shorthand link: [#](#) . The text is also filled in by odoc in this case. + +This is a reference to [foo](#val-foo) . References can have replacement text: [the value foo](#val-foo) . Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: [**bold**](#val-foo) , [_italic_](#val-foo) , [_emphasis_](#val-foo) , [super script](#val-foo) , [sub script](#val-foo) , and [code](#val-foo) . It's also possible to surround a reference in a style: **[foo](#val-foo)** . References can't be nested inside references, and links and references can't be nested inside each other. + +# Preformatted text + +This is a code block: + +let foo = () +(** There are some nested comments in here, but an unpaired comment + terminator would terminate the whole doc surrounding comment. It's + best to keep code blocks no wider than 72 characters. *) + +let bar = + ignore foo + +There are also verbatim blocks: + +``` +The main difference is these don't get syntax highlighting. +``` + +# Lists + +- This is a + +- shorthand bulleted list, + +- and the paragraphs in each list item support _styling_ . + +1. This is a + +2. shorthand numbered list. + +- Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break + +just creates a paragraph outside the list. + +- Similarly, inserting a blank line between two list items + +- creates two separate lists. + +- To get around this limitation, one + + can use explicitly-delimited lists. + +- This one is bulleted, + +1. but there is also the numbered variant. + +- - lists + + - can be nested + + - and can include references + + - [foo](#val-foo) + +# Unicode + +The parser supports any ASCII-compatible encoding, in particuλar UTF-8. + +# Raw HTML + +Raw HTML can be as inline elements into sentences. + + +
+ If the raw HTML is the only thing in a paragraph, it is treated as a block + element, and won't be wrapped in paragraph tags by the HTML generator. +
+ + +# Modules + +@[X](Markup.X.md): + +@[X](Markup.X.md): + +@[Y](Markup.Y.md): + +# Tags + +Each comment can end with zero or more tags. Here are some examples: + +@author: antron + +@deprecated: + +@parameter foo: + +@raises Failure: + +@returns: + +@see [#](#): + +@see foo.ml: + +@see Foo: + +@since: 0 + +@before 1.0: + +@version: -1 + + + +###### val foo : + +> unit + + +Comments in structure items + +Some modules to support references. + + + +###### module [X](Markup.X.md) + + + +###### module [Y](Markup.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.M'.md b/test/generators/markdown/Module.M'.md new file mode 100644 index 0000000000..550397744a --- /dev/null +++ b/test/generators/markdown/Module.M'.md @@ -0,0 +1,5 @@ +Module + +M' + +Module Module.M' \ No newline at end of file diff --git a/test/generators/markdown/Module.Mutually.md b/test/generators/markdown/Module.Mutually.md new file mode 100644 index 0000000000..374a3d93b0 --- /dev/null +++ b/test/generators/markdown/Module.Mutually.md @@ -0,0 +1,5 @@ +Module + +Mutually + +Module Module.Mutually \ No newline at end of file diff --git a/test/generators/markdown/Module.Recursive.md b/test/generators/markdown/Module.Recursive.md new file mode 100644 index 0000000000..ea7f4018e3 --- /dev/null +++ b/test/generators/markdown/Module.Recursive.md @@ -0,0 +1,5 @@ +Module + +Recursive + +Module Module.Recursive \ No newline at end of file diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md new file mode 100644 index 0000000000..b94853643b --- /dev/null +++ b/test/generators/markdown/Module.md @@ -0,0 +1,73 @@ +Module + +Module Module + +Foo. + + + +###### val foo : + +> unit + + +The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See + + + +###### module type [S](Module.module-type-S.md) + + + +###### module type S1 + + + +###### module type S2 = + +> [S](Module.module-type-S.md) + + + + +###### module type [S3](Module.module-type-S3.md) + + + +###### module type [S4](Module.module-type-S4.md) + + + +###### module type [S5](Module.module-type-S5.md) + + + +###### type ('a, 'b) result + + + +###### module type [S6](Module.module-type-S6.md) + + + +###### module [M'](Module.M'.md) + + + +###### module type [S7](Module.module-type-S7.md) + + + +###### module type [S8](Module.module-type-S8.md) + + + +###### module type [S9](Module.module-type-S9.md) + + + +###### module [Mutually](Module.Mutually.md) + + + +###### module [Recursive](Module.Recursive.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S.M.md b/test/generators/markdown/Module.module-type-S.M.md new file mode 100644 index 0000000000..238cbef37f --- /dev/null +++ b/test/generators/markdown/Module.module-type-S.M.md @@ -0,0 +1,7 @@ +Module + +S + +M + +Module S.M \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S.md b/test/generators/markdown/Module.module-type-S.md new file mode 100644 index 0000000000..20c1c69b62 --- /dev/null +++ b/test/generators/markdown/Module.module-type-S.md @@ -0,0 +1,25 @@ +Module + +S + +Module type Module.S + + + +###### type t + + + +###### type u + + + +###### type 'a v + + + +###### type ('a, 'b) w + + + +###### module [M](Module.module-type-S.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S3.M.md b/test/generators/markdown/Module.module-type-S3.M.md new file mode 100644 index 0000000000..9e799a6475 --- /dev/null +++ b/test/generators/markdown/Module.module-type-S3.M.md @@ -0,0 +1,7 @@ +Module + +S3 + +M + +Module S3.M \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S3.md b/test/generators/markdown/Module.module-type-S3.md new file mode 100644 index 0000000000..868e009fec --- /dev/null +++ b/test/generators/markdown/Module.module-type-S3.md @@ -0,0 +1,31 @@ +Module + +S3 + +Module type Module.S3 + + + +###### type t = + +> int + + + + +###### type u = + +> string + + + + +###### type 'a v + + + +###### type ('a, 'b) w + + + +###### module [M](Module.module-type-S3.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S4.M.md b/test/generators/markdown/Module.module-type-S4.M.md new file mode 100644 index 0000000000..4b2154399d --- /dev/null +++ b/test/generators/markdown/Module.module-type-S4.M.md @@ -0,0 +1,7 @@ +Module + +S4 + +M + +Module S4.M \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S4.md b/test/generators/markdown/Module.module-type-S4.md new file mode 100644 index 0000000000..90b5739bde --- /dev/null +++ b/test/generators/markdown/Module.module-type-S4.md @@ -0,0 +1,21 @@ +Module + +S4 + +Module type Module.S4 + + + +###### type u + + + +###### type 'a v + + + +###### type ('a, 'b) w + + + +###### module [M](Module.module-type-S4.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S5.M.md b/test/generators/markdown/Module.module-type-S5.M.md new file mode 100644 index 0000000000..5edf58c4bc --- /dev/null +++ b/test/generators/markdown/Module.module-type-S5.M.md @@ -0,0 +1,7 @@ +Module + +S5 + +M + +Module S5.M \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S5.md b/test/generators/markdown/Module.module-type-S5.md new file mode 100644 index 0000000000..cd1df21cb6 --- /dev/null +++ b/test/generators/markdown/Module.module-type-S5.md @@ -0,0 +1,21 @@ +Module + +S5 + +Module type Module.S5 + + + +###### type t + + + +###### type u + + + +###### type ('a, 'b) w + + + +###### module [M](Module.module-type-S5.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S6.M.md b/test/generators/markdown/Module.module-type-S6.M.md new file mode 100644 index 0000000000..84e4d7f7ab --- /dev/null +++ b/test/generators/markdown/Module.module-type-S6.M.md @@ -0,0 +1,7 @@ +Module + +S6 + +M + +Module S6.M \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S6.md b/test/generators/markdown/Module.module-type-S6.md new file mode 100644 index 0000000000..64bd1a945f --- /dev/null +++ b/test/generators/markdown/Module.module-type-S6.md @@ -0,0 +1,21 @@ +Module + +S6 + +Module type Module.S6 + + + +###### type t + + + +###### type u + + + +###### type 'a v + + + +###### module [M](Module.module-type-S6.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S7.md b/test/generators/markdown/Module.module-type-S7.md new file mode 100644 index 0000000000..924007faa2 --- /dev/null +++ b/test/generators/markdown/Module.module-type-S7.md @@ -0,0 +1,27 @@ +Module + +S7 + +Module type Module.S7 + + + +###### type t + + + +###### type u + + + +###### type 'a v + + + +###### type ('a, 'b) w + + + +###### module M = + +> [M'](Module.M'.md) diff --git a/test/generators/markdown/Module.module-type-S8.md b/test/generators/markdown/Module.module-type-S8.md new file mode 100644 index 0000000000..4082efdf51 --- /dev/null +++ b/test/generators/markdown/Module.module-type-S8.md @@ -0,0 +1,21 @@ +Module + +S8 + +Module type Module.S8 + + + +###### type t + + + +###### type u + + + +###### type 'a v + + + +###### type ('a, 'b) w \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S9.md b/test/generators/markdown/Module.module-type-S9.md new file mode 100644 index 0000000000..d73b88bb86 --- /dev/null +++ b/test/generators/markdown/Module.module-type-S9.md @@ -0,0 +1,5 @@ +Module + +S9 + +Module type Module.S9 \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.md b/test/generators/markdown/Module_type_alias.md new file mode 100644 index 0000000000..d5f616e8d0 --- /dev/null +++ b/test/generators/markdown/Module_type_alias.md @@ -0,0 +1,34 @@ +Module_type_alias + +Module Module_type_alias + +Module Type Aliases + + + +###### module type [A](Module_type_alias.module-type-A.md) + + + +###### module type [B](Module_type_alias.module-type-B.md) + + + +###### module type D = + +> [A](Module_type_alias.module-type-A.md) + + + + +###### module type [E](Module_type_alias.module-type-E.md) + + + +###### module type [G](Module_type_alias.module-type-G.md) + + + +###### module type I = + +> [B](Module_type_alias.module-type-B.md) diff --git a/test/generators/markdown/Module_type_alias.module-type-A.md b/test/generators/markdown/Module_type_alias.module-type-A.md new file mode 100644 index 0000000000..38f54c5a0d --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-A.md @@ -0,0 +1,9 @@ +Module_type_alias + +A + +Module type Module_type_alias.A + + + +###### type a \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md b/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md new file mode 100644 index 0000000000..4f2ff51831 --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md @@ -0,0 +1,11 @@ +Module_type_alias + +B + +1-C + +Parameter B.1-C + + + +###### type c \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-B.md b/test/generators/markdown/Module_type_alias.module-type-B.md new file mode 100644 index 0000000000..15d54b5c3c --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-B.md @@ -0,0 +1,17 @@ +Module_type_alias + +B + +Module type Module_type_alias.B + +# Parameters + + + +###### module [C](Module_type_alias.module-type-B.argument-1-C.md) + +# Signature + + + +###### type b \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md b/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md new file mode 100644 index 0000000000..eb3cb558f8 --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md @@ -0,0 +1,11 @@ +Module_type_alias + +E + +1-F + +Parameter E.1-F + + + +###### type f \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md b/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md new file mode 100644 index 0000000000..0b64fb5c68 --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md @@ -0,0 +1,11 @@ +Module_type_alias + +E + +2-C + +Parameter E.2-C + + + +###### type c \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-E.md b/test/generators/markdown/Module_type_alias.module-type-E.md new file mode 100644 index 0000000000..8aac6c36e1 --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-E.md @@ -0,0 +1,21 @@ +Module_type_alias + +E + +Module type Module_type_alias.E + +# Parameters + + + +###### module [F](Module_type_alias.module-type-E.argument-1-F.md) + + + +###### module [C](Module_type_alias.module-type-E.argument-2-C.md) + +# Signature + + + +###### type b \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md b/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md new file mode 100644 index 0000000000..89ce922b41 --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md @@ -0,0 +1,11 @@ +Module_type_alias + +G + +1-H + +Parameter G.1-H + + + +###### type h \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.module-type-G.md b/test/generators/markdown/Module_type_alias.module-type-G.md new file mode 100644 index 0000000000..c6806b5e3e --- /dev/null +++ b/test/generators/markdown/Module_type_alias.module-type-G.md @@ -0,0 +1,17 @@ +Module_type_alias + +G + +Module type Module_type_alias.G + +# Parameters + + + +###### module [H](Module_type_alias.module-type-G.argument-1-H.md) + +# Signature + + + +###### type a \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.md b/test/generators/markdown/Module_type_subst.Basic.md new file mode 100644 index 0000000000..734fd96a11 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.md @@ -0,0 +1,29 @@ +Module_type_subst + +Basic + +Module Module_type_subst.Basic + + + +###### module type [u](Module_type_subst.Basic.module-type-u.md) + + + +###### module type [with_](Module_type_subst.Basic.module-type-with_.md) + + + +###### module type [u2](Module_type_subst.Basic.module-type-u2.md) + + + +###### module type [with_2](Module_type_subst.Basic.module-type-with_2.md) + + + +###### module type [a](Module_type_subst.Basic.module-type-a.md) + + + +###### module type [c](Module_type_subst.Basic.module-type-c.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md new file mode 100644 index 0000000000..648f235fde --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +a + +M + +Module a.M \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-a.md b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md new file mode 100644 index 0000000000..686474eb3b --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md @@ -0,0 +1,18 @@ +Module_type_subst + +Basic + +a + +Module type Basic.a + + + +###### module type b = + +> [s](Module_type_subst.module-type-s.md) + + + + +###### module [M](Module_type_subst.Basic.module-type-a.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md new file mode 100644 index 0000000000..1fb1f73299 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +c + +M + +Module c.M \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-c.md b/test/generators/markdown/Module_type_subst.Basic.module-type-c.md new file mode 100644 index 0000000000..a945120bc4 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-c.md @@ -0,0 +1,11 @@ +Module_type_subst + +Basic + +c + +Module type Basic.c + + + +###### module [M](Module_type_subst.Basic.module-type-c.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md new file mode 100644 index 0000000000..2ca2303d9b --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md @@ -0,0 +1,11 @@ +Module_type_subst + +Basic + +u + +Module type Basic.u + + + +###### module type [T](Module_type_subst.Basic.module-type-u.module-type-T.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md new file mode 100644 index 0000000000..08317bf3b5 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +u + +T + +Module type u.T \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md new file mode 100644 index 0000000000..674e50e124 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +u2 + +M + +Module u2.M \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md new file mode 100644 index 0000000000..73677bfe06 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md @@ -0,0 +1,15 @@ +Module_type_subst + +Basic + +u2 + +Module type Basic.u2 + + + +###### module type [T](Module_type_subst.Basic.module-type-u2.module-type-T.md) + + + +###### module [M](Module_type_subst.Basic.module-type-u2.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md new file mode 100644 index 0000000000..71e89f2532 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +u2 + +T + +Module type u2.T \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md new file mode 100644 index 0000000000..21ae5e5c3c --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md @@ -0,0 +1,13 @@ +Module_type_subst + +Basic + +with_ + +Module type Basic.with_ + + + +###### module type T = + +> [s](Module_type_subst.module-type-s.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md new file mode 100644 index 0000000000..7219c05c96 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +with_2 + +M + +Module with_2.M \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md new file mode 100644 index 0000000000..6ad00afb5e --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md @@ -0,0 +1,15 @@ +Module_type_subst + +Basic + +with_2 + +Module type Basic.with_2 + + + +###### module type [T](Module_type_subst.Basic.module-type-with_2.module-type-T.md) + + + +###### module [M](Module_type_subst.Basic.module-type-with_2.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md new file mode 100644 index 0000000000..471745a3ed --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md @@ -0,0 +1,9 @@ +Module_type_subst + +Basic + +with_2 + +T + +Module type with_2.T \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Local.md b/test/generators/markdown/Module_type_subst.Local.md new file mode 100644 index 0000000000..5f20e8922d --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Local.md @@ -0,0 +1,27 @@ +Module_type_subst + +Local + +Module Module_type_subst.Local + + + +###### type local := + +> int * int + + + + +###### module type [local](Module_type_subst.Local.module-type-local.md) + + + +###### module type w = + +> [local](Module_type_subst.Local.module-type-local.md) + + + + +###### module type [s](Module_type_subst.Local.module-type-s.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Local.module-type-local.md b/test/generators/markdown/Module_type_subst.Local.module-type-local.md new file mode 100644 index 0000000000..9f307328dc --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Local.module-type-local.md @@ -0,0 +1,13 @@ +Module_type_subst + +Local + +local + +Module type Local.local + + + +###### type t = + +> [local](Module_type_subst.Local.md#type-local) diff --git a/test/generators/markdown/Module_type_subst.Local.module-type-s.md b/test/generators/markdown/Module_type_subst.Local.module-type-s.md new file mode 100644 index 0000000000..4373a29658 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Local.module-type-s.md @@ -0,0 +1,7 @@ +Module_type_subst + +Local + +s + +Module type Local.s \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.md b/test/generators/markdown/Module_type_subst.Nested.md new file mode 100644 index 0000000000..212fd0e912 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.md @@ -0,0 +1,17 @@ +Module_type_subst + +Nested + +Module Module_type_subst.Nested + + + +###### module type [nested](Module_type_subst.Nested.module-type-nested.md) + + + +###### module type [with_](Module_type_subst.Nested.module-type-with_.md) + + + +###### module type [with_subst](Module_type_subst.Nested.module-type-with_subst.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md new file mode 100644 index 0000000000..7657eeb234 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md @@ -0,0 +1,13 @@ +Module_type_subst + +Nested + +nested + +N + +Module nested.N + + + +###### module type [t](Module_type_subst.Nested.module-type-nested.N.module-type-t.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md new file mode 100644 index 0000000000..c65192e1a7 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md @@ -0,0 +1,11 @@ +Module_type_subst + +Nested + +nested + +N + +t + +Module type N.t \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md new file mode 100644 index 0000000000..f2920570d3 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md @@ -0,0 +1,11 @@ +Module_type_subst + +Nested + +nested + +Module type Nested.nested + + + +###### module [N](Module_type_subst.Nested.module-type-nested.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md new file mode 100644 index 0000000000..4132fb2089 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md @@ -0,0 +1,15 @@ +Module_type_subst + +Nested + +with_ + +N + +Module with_.N + + + +###### module type t = + +> [s](Module_type_subst.module-type-s.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md new file mode 100644 index 0000000000..1c2b457152 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md @@ -0,0 +1,11 @@ +Module_type_subst + +Nested + +with_ + +Module type Nested.with_ + + + +###### module [N](Module_type_subst.Nested.module-type-with_.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md new file mode 100644 index 0000000000..83beb9f3e0 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md @@ -0,0 +1,9 @@ +Module_type_subst + +Nested + +with_subst + +N + +Module with_subst.N \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md new file mode 100644 index 0000000000..a34e5dab1f --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md @@ -0,0 +1,11 @@ +Module_type_subst + +Nested + +with_subst + +Module type Nested.with_subst + + + +###### module [N](Module_type_subst.Nested.module-type-with_subst.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.md b/test/generators/markdown/Module_type_subst.Structural.md new file mode 100644 index 0000000000..46195b2618 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.md @@ -0,0 +1,13 @@ +Module_type_subst + +Structural + +Module Module_type_subst.Structural + + + +###### module type [u](Module_type_subst.Structural.module-type-u.md) + + + +###### module type [w](Module_type_subst.Structural.module-type-w.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md new file mode 100644 index 0000000000..984293f679 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md @@ -0,0 +1,11 @@ +Module_type_subst + +Structural + +u + +Module type Structural.u + + + +###### module type [a](Module_type_subst.Structural.module-type-u.module-type-a.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md new file mode 100644 index 0000000000..ea06df5d9d --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md @@ -0,0 +1,13 @@ +Module_type_subst + +Structural + +u + +a + +Module type u.a + + + +###### module type [b](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md new file mode 100644 index 0000000000..fbae4ccea5 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md @@ -0,0 +1,15 @@ +Module_type_subst + +Structural + +u + +a + +b + +Module type a.b + + + +###### module type [c](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md new file mode 100644 index 0000000000..53557518bb --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md @@ -0,0 +1,21 @@ +Module_type_subst + +Structural + +u + +a + +b + +c + +Module type b.c + + + +###### type t = + + + +######    | A of [t](#type-t) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md new file mode 100644 index 0000000000..06d74e7c1b --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md @@ -0,0 +1,11 @@ +Module_type_subst + +Structural + +w + +Module type Structural.w + + + +###### module type [a](Module_type_subst.Structural.module-type-w.module-type-a.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md new file mode 100644 index 0000000000..81e23a97d1 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md @@ -0,0 +1,13 @@ +Module_type_subst + +Structural + +w + +a + +Module type w.a + + + +###### module type [b](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md new file mode 100644 index 0000000000..5902db4242 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md @@ -0,0 +1,15 @@ +Module_type_subst + +Structural + +w + +a + +b + +Module type a.b + + + +###### module type [c](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md new file mode 100644 index 0000000000..57a7ec6519 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md @@ -0,0 +1,21 @@ +Module_type_subst + +Structural + +w + +a + +b + +c + +Module type b.c + + + +###### type t = + + + +######    | A of [t](#type-t) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.md b/test/generators/markdown/Module_type_subst.md new file mode 100644 index 0000000000..cab0e249c1 --- /dev/null +++ b/test/generators/markdown/Module_type_subst.md @@ -0,0 +1,23 @@ +Module_type_subst + +Module Module_type_subst + + + +###### module [Local](Module_type_subst.Local.md) + + + +###### module type [s](Module_type_subst.module-type-s.md) + + + +###### module [Basic](Module_type_subst.Basic.md) + + + +###### module [Nested](Module_type_subst.Nested.md) + + + +###### module [Structural](Module_type_subst.Structural.md) \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.module-type-s.md b/test/generators/markdown/Module_type_subst.module-type-s.md new file mode 100644 index 0000000000..1d0b8502df --- /dev/null +++ b/test/generators/markdown/Module_type_subst.module-type-s.md @@ -0,0 +1,5 @@ +Module_type_subst + +s + +Module type Module_type_subst.s \ No newline at end of file diff --git a/test/generators/markdown/Nested.F.argument-1-Arg1.md b/test/generators/markdown/Nested.F.argument-1-Arg1.md new file mode 100644 index 0000000000..9a7e3f93dc --- /dev/null +++ b/test/generators/markdown/Nested.F.argument-1-Arg1.md @@ -0,0 +1,26 @@ +Nested + +F + +1-Arg1 + +Parameter F.1-Arg1 + +# Type + + + +###### type t + +Some type. + +# Values + + + +###### val y : + +> [t](#type-t) + + +The value of y. \ No newline at end of file diff --git a/test/generators/markdown/Nested.F.argument-2-Arg2.md b/test/generators/markdown/Nested.F.argument-2-Arg2.md new file mode 100644 index 0000000000..d653476a01 --- /dev/null +++ b/test/generators/markdown/Nested.F.argument-2-Arg2.md @@ -0,0 +1,15 @@ +Nested + +F + +2-Arg2 + +Parameter F.2-Arg2 + +# Type + + + +###### type t + +Some type. \ No newline at end of file diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md new file mode 100644 index 0000000000..3aaee73f28 --- /dev/null +++ b/test/generators/markdown/Nested.F.md @@ -0,0 +1,32 @@ +Nested + +F + +Module Nested.F + +This is a functor F. + +Some additional comments. + +# Parameters + + + +###### module [Arg1](Nested.F.argument-1-Arg1.md) + + + +###### module [Arg2](Nested.F.argument-2-Arg2.md) + +# Signature + +# Type + + + +###### type t = + +> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) + + +Some type. \ No newline at end of file diff --git a/test/generators/markdown/Nested.X.md b/test/generators/markdown/Nested.X.md new file mode 100644 index 0000000000..5411347c6a --- /dev/null +++ b/test/generators/markdown/Nested.X.md @@ -0,0 +1,28 @@ +Nested + +X + +Module Nested.X + +This is module X. + +Some additional comments. + +# Type + + + +###### type t + +Some type. + +# Values + + + +###### val x : + +> [t](#type-t) + + +The value of x. \ No newline at end of file diff --git a/test/generators/markdown/Nested.inherits.md b/test/generators/markdown/Nested.inherits.md new file mode 100644 index 0000000000..815d77cf95 --- /dev/null +++ b/test/generators/markdown/Nested.inherits.md @@ -0,0 +1,9 @@ +Nested + +inherits + +Class Nested.inherits + + + +###### inherit [z](Nested.z.md) \ No newline at end of file diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md new file mode 100644 index 0000000000..82a838a8e9 --- /dev/null +++ b/test/generators/markdown/Nested.md @@ -0,0 +1,41 @@ +Nested + +Module Nested + +This comment needs to be here before #235 is fixed. + +# Module + + + +###### module [X](Nested.X.md) + +This is module X. + +# Module type + + + +###### module type [Y](Nested.module-type-Y.md) + +This is module type Y. + +# Functor + + + +###### module [F](Nested.F.md) + +This is a functor F. + +# Class + + + +###### class virtual [z](Nested.z.md) + +This is class z. + + + +###### class virtual [inherits](Nested.inherits.md) \ No newline at end of file diff --git a/test/generators/markdown/Nested.module-type-Y.md b/test/generators/markdown/Nested.module-type-Y.md new file mode 100644 index 0000000000..258ac10da4 --- /dev/null +++ b/test/generators/markdown/Nested.module-type-Y.md @@ -0,0 +1,28 @@ +Nested + +Y + +Module type Nested.Y + +This is module type Y. + +Some additional comments. + +# Type + + + +###### type t + +Some type. + +# Values + + + +###### val y : + +> [t](#type-t) + + +The value of y. \ No newline at end of file diff --git a/test/generators/markdown/Nested.z.md b/test/generators/markdown/Nested.z.md new file mode 100644 index 0000000000..f8117cf8b1 --- /dev/null +++ b/test/generators/markdown/Nested.z.md @@ -0,0 +1,42 @@ +Nested + +z + +Class Nested.z + +This is class z. + +Some additional comments. + + + +###### val y : + +> int + + +Some value. + + + +###### val mutable virtual y' : + +> int + + +# Methods + + + +###### method z : + +> int + + +Some method. + + + +###### method private virtual z' : + +> int diff --git a/test/generators/markdown/Ocamlary.Aliases.E.md b/test/generators/markdown/Ocamlary.Aliases.E.md new file mode 100644 index 0000000000..50d2823062 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.E.md @@ -0,0 +1,17 @@ +Ocamlary + +Aliases + +E + +Module Aliases.E + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.A.md b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md new file mode 100644 index 0000000000..ec75ea14dc --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md @@ -0,0 +1,19 @@ +Ocamlary + +Aliases + +Foo + +A + +Module Foo.A + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.B.md b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md new file mode 100644 index 0000000000..ed7af4df80 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md @@ -0,0 +1,19 @@ +Ocamlary + +Aliases + +Foo + +B + +Module Foo.B + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.C.md b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md new file mode 100644 index 0000000000..9a692943db --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md @@ -0,0 +1,19 @@ +Ocamlary + +Aliases + +Foo + +C + +Module Foo.C + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.D.md b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md new file mode 100644 index 0000000000..f0b4d0856c --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md @@ -0,0 +1,19 @@ +Ocamlary + +Aliases + +Foo + +D + +Module Foo.D + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.E.md b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md new file mode 100644 index 0000000000..e5f3335b55 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md @@ -0,0 +1,19 @@ +Ocamlary + +Aliases + +Foo + +E + +Module Foo.E + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.md b/test/generators/markdown/Ocamlary.Aliases.Foo.md new file mode 100644 index 0000000000..249a41ef1f --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.md @@ -0,0 +1,27 @@ +Ocamlary + +Aliases + +Foo + +Module Aliases.Foo + + + +###### module [A](Ocamlary.Aliases.Foo.A.md) + + + +###### module [B](Ocamlary.Aliases.Foo.B.md) + + + +###### module [C](Ocamlary.Aliases.Foo.C.md) + + + +###### module [D](Ocamlary.Aliases.Foo.D.md) + + + +###### module [E](Ocamlary.Aliases.Foo.E.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.Y.md b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md new file mode 100644 index 0000000000..7d3cdc6d2b --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md @@ -0,0 +1,19 @@ +Ocamlary + +Aliases + +P1 + +Y + +Module P1.Y + + + +###### type t + + + +###### val id : + +> [t](#type-t) -> [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.md b/test/generators/markdown/Ocamlary.Aliases.P1.md new file mode 100644 index 0000000000..32d6c464c7 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.P1.md @@ -0,0 +1,11 @@ +Ocamlary + +Aliases + +P1 + +Module Aliases.P1 + + + +###### module [Y](Ocamlary.Aliases.P1.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Aliases.P2.md b/test/generators/markdown/Ocamlary.Aliases.P2.md new file mode 100644 index 0000000000..3237d3de13 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.P2.md @@ -0,0 +1,13 @@ +Ocamlary + +Aliases + +P2 + +Module Aliases.P2 + + + +###### module Z = + +> [Z](Ocamlary.Aliases.P1.Y.md) diff --git a/test/generators/markdown/Ocamlary.Aliases.Std.md b/test/generators/markdown/Ocamlary.Aliases.Std.md new file mode 100644 index 0000000000..cd9eb9c163 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.Std.md @@ -0,0 +1,41 @@ +Ocamlary + +Aliases + +Std + +Module Aliases.Std + + + +###### module A = + +> [Foo.A](Ocamlary.Aliases.Foo.A.md) + + + + +###### module B = + +> [Foo.B](Ocamlary.Aliases.Foo.B.md) + + + + +###### module C = + +> [Foo.C](Ocamlary.Aliases.Foo.C.md) + + + + +###### module D = + +> [Foo.D](Ocamlary.Aliases.Foo.D.md) + + + + +###### module E = + +> [Foo.E](Ocamlary.Aliases.Foo.E.md) diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md new file mode 100644 index 0000000000..fd2137c3db --- /dev/null +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -0,0 +1,143 @@ +Ocamlary + +Aliases + +Module Ocamlary.Aliases + +Let's imitate jst's layout. + + + +###### module [Foo](Ocamlary.Aliases.Foo.md) + + + +###### module A' = + +> [Foo.A](Ocamlary.Aliases.Foo.A.md) + + + + +###### type tata = + +> [Foo.A.t](Ocamlary.Aliases.Foo.A.md#type-t) + + + + +###### type tbtb = + +> [Foo.B.t](Ocamlary.Aliases.Foo.B.md#type-t) + + + + +###### type tete + + + +###### type tata' = + +> [A'.t](Ocamlary.Aliases.Foo.A.md#type-t) + + + + +###### type tete2 = + +> [Foo.E.t](Ocamlary.Aliases.Foo.E.md#type-t) + + + + +###### module [Std](Ocamlary.Aliases.Std.md) + + + +###### type stde = + +> [Std.E.t](Ocamlary.Aliases.Foo.E.md#type-t) + + +### include of Foo + +--- + +Just for giggle, let's see what happens when we include [Foo](Ocamlary.Aliases.Foo.md) . + + + +###### module A = + +> [Foo.A](Ocamlary.Aliases.Foo.A.md) + + + + +###### module B = + +> [Foo.B](Ocamlary.Aliases.Foo.B.md) + + + + +###### module C = + +> [Foo.C](Ocamlary.Aliases.Foo.C.md) + + + + +###### module D = + +> [Foo.D](Ocamlary.Aliases.Foo.D.md) + + + + +###### module [E](Ocamlary.Aliases.E.md) + + + +###### type testa = + +> [A.t](Ocamlary.Aliases.Foo.A.md#type-t) + + +And also, let's refer to [A.t](Ocamlary.Aliases.Foo.A.md#type-t) and [Foo.B.id](Ocamlary.Aliases.Foo.B.md#val-id) + + + +###### module [P1](Ocamlary.Aliases.P1.md) + + + +###### module [P2](Ocamlary.Aliases.P2.md) + + + +###### module X1 = + +> [P2.Z](Ocamlary.Aliases.P1.Y.md) + + + + +###### module X2 = + +> [P2.Z](Ocamlary.Aliases.P1.Y.md) + + + + +###### type p1 = + +> [X1.t](Ocamlary.Aliases.P1.Y.md#type-t) + + + + +###### type p2 = + +> [X2.t](Ocamlary.Aliases.P1.Y.md#type-t) diff --git a/test/generators/markdown/Ocamlary.Buffer.md b/test/generators/markdown/Ocamlary.Buffer.md new file mode 100644 index 0000000000..f808f3cb96 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Buffer.md @@ -0,0 +1,13 @@ +Ocamlary + +Buffer + +Module Ocamlary.Buffer + +References are resolved after everything, so {!Buffer.t} won't resolve. + + + +###### val f : + +> int -> unit diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md new file mode 100644 index 0000000000..095521c60f --- /dev/null +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md @@ -0,0 +1,19 @@ +Ocamlary + +CanonicalTest + +Base + +List + +Module Base.List + + + +###### type 'a t + + + +###### val id : + +> 'a [t](#type-t) -> 'a [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md new file mode 100644 index 0000000000..098cbf6612 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md @@ -0,0 +1,11 @@ +Ocamlary + +CanonicalTest + +Base + +Module CanonicalTest.Base + + + +###### module [List](Ocamlary.CanonicalTest.Base.List.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md new file mode 100644 index 0000000000..0b028a1208 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md @@ -0,0 +1,19 @@ +Ocamlary + +CanonicalTest + +Base_Tests + +C + +Module Base_Tests.C + + + +###### type 'a t + + + +###### val id : + +> 'a [t](#type-t) -> 'a [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md new file mode 100644 index 0000000000..54d43b3179 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md @@ -0,0 +1,38 @@ +Ocamlary + +CanonicalTest + +Base_Tests + +Module CanonicalTest.Base_Tests + + + +###### module [C](Ocamlary.CanonicalTest.Base_Tests.C.md) + + + +###### module L = + +> [Base.List](Ocamlary.CanonicalTest.Base.List.md) + + + + +###### val foo : + +> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) + + + + +###### val bar : + +> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) + + + + +###### val baz : + +> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> unit diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md new file mode 100644 index 0000000000..78e99d0b43 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md @@ -0,0 +1,20 @@ +Ocamlary + +CanonicalTest + +List_modif + +Module CanonicalTest.List_modif + + + +###### type 'c t = + +> 'c [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) + + + + +###### val id : + +> 'a [t](#type-t) -> 'a [t](#type-t) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.md b/test/generators/markdown/Ocamlary.CanonicalTest.md new file mode 100644 index 0000000000..fb70bd64b4 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CanonicalTest.md @@ -0,0 +1,17 @@ +Ocamlary + +CanonicalTest + +Module Ocamlary.CanonicalTest + + + +###### module [Base](Ocamlary.CanonicalTest.Base.md) + + + +###### module [Base_Tests](Ocamlary.CanonicalTest.Base_Tests.md) + + + +###### module [List_modif](Ocamlary.CanonicalTest.List_modif.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..b30db9b8b2 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,20 @@ +Ocamlary + +CollectionModule + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md new file mode 100644 index 0000000000..0a2e862ef5 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -0,0 +1,30 @@ +Ocamlary + +CollectionModule + +InnerModuleA + +Module CollectionModule.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.CollectionModule.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..182eddd512 --- /dev/null +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,20 @@ +Ocamlary + +CollectionModule + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md new file mode 100644 index 0000000000..169ea86fcb --- /dev/null +++ b/test/generators/markdown/Ocamlary.CollectionModule.md @@ -0,0 +1,32 @@ +Ocamlary + +CollectionModule + +Module Ocamlary.CollectionModule + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.CollectionModule.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md new file mode 100644 index 0000000000..f3034432cc --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md @@ -0,0 +1,17 @@ +Ocamlary + +Dep1 + +X + +Y + +c + +Class Y.c + + + +###### method m : + +> int diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.md new file mode 100644 index 0000000000..0fea5ce7ab --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep1 + +X + +Y + +Module X.Y + + + +###### class [c](Ocamlary.Dep1.X.Y.c.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep1.X.md b/test/generators/markdown/Ocamlary.Dep1.X.md new file mode 100644 index 0000000000..582fb90d84 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep1.X.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep1 + +X + +Module Dep1.X + + + +###### module [Y](Ocamlary.Dep1.X.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep1.md b/test/generators/markdown/Ocamlary.Dep1.md new file mode 100644 index 0000000000..16bbce007a --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep1.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep1 + +Module Ocamlary.Dep1 + + + +###### module type [S](Ocamlary.Dep1.module-type-S.md) + + + +###### module [X](Ocamlary.Dep1.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md new file mode 100644 index 0000000000..8314f9e07c --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md @@ -0,0 +1,15 @@ +Ocamlary + +Dep1 + +S + +c + +Class S.c + + + +###### method m : + +> int diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md new file mode 100644 index 0000000000..e8ccdaf4af --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep1 + +S + +Module type Dep1.S + + + +###### class [c](Ocamlary.Dep1.module-type-S.c.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep11.md b/test/generators/markdown/Ocamlary.Dep11.md new file mode 100644 index 0000000000..5e163d7858 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep11.md @@ -0,0 +1,9 @@ +Ocamlary + +Dep11 + +Module Ocamlary.Dep11 + + + +###### module type [S](Ocamlary.Dep11.module-type-S.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md new file mode 100644 index 0000000000..e9c13f0e3d --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md @@ -0,0 +1,15 @@ +Ocamlary + +Dep11 + +S + +c + +Class S.c + + + +###### method m : + +> int diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md new file mode 100644 index 0000000000..3e392705b3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep11 + +S + +Module type Dep11.S + + + +###### class [c](Ocamlary.Dep11.module-type-S.c.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md new file mode 100644 index 0000000000..43d9817e56 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep12 + +1-Arg + +Parameter Dep12.1-Arg + + + +###### module type S \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep12.md b/test/generators/markdown/Ocamlary.Dep12.md new file mode 100644 index 0000000000..1bdf6011bc --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep12.md @@ -0,0 +1,19 @@ +Ocamlary + +Dep12 + +Module Ocamlary.Dep12 + +# Parameters + + + +###### module [Arg](Ocamlary.Dep12.argument-1-Arg.md) + +# Signature + + + +###### module type T = + +> [Arg.S](Ocamlary.Dep12.argument-1-Arg.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.Dep13.c.md b/test/generators/markdown/Ocamlary.Dep13.c.md new file mode 100644 index 0000000000..6d5500ff9e --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep13.c.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep13 + +c + +Class Dep13.c + + + +###### method m : + +> int diff --git a/test/generators/markdown/Ocamlary.Dep13.md b/test/generators/markdown/Ocamlary.Dep13.md new file mode 100644 index 0000000000..f54fd53492 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep13.md @@ -0,0 +1,9 @@ +Ocamlary + +Dep13 + +Module Ocamlary.Dep13 + + + +###### class [c](Ocamlary.Dep13.c.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep2.A.md b/test/generators/markdown/Ocamlary.Dep2.A.md new file mode 100644 index 0000000000..c89104328f --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep2.A.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep2 + +A + +Module Dep2.A + + + +###### module Y : + +> [Arg.S](Ocamlary.Dep2.argument-1-Arg.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md new file mode 100644 index 0000000000..1ddafd4b60 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md @@ -0,0 +1,15 @@ +Ocamlary + +Dep2 + +1-Arg + +X + +Module 1-Arg.X + + + +###### module Y : + +> [S](Ocamlary.Dep2.argument-1-Arg.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md new file mode 100644 index 0000000000..cc9e652959 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md @@ -0,0 +1,15 @@ +Ocamlary + +Dep2 + +1-Arg + +Parameter Dep2.1-Arg + + + +###### module type S + + + +###### module [X](Ocamlary.Dep2.argument-1-Arg.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep2.md b/test/generators/markdown/Ocamlary.Dep2.md new file mode 100644 index 0000000000..beb8e747a0 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep2.md @@ -0,0 +1,23 @@ +Ocamlary + +Dep2 + +Module Ocamlary.Dep2 + +# Parameters + + + +###### module [Arg](Ocamlary.Dep2.argument-1-Arg.md) + +# Signature + + + +###### module [A](Ocamlary.Dep2.A.md) + + + +###### module B = + +> [A.Y](Ocamlary.Dep2.A.md#module-Y) diff --git a/test/generators/markdown/Ocamlary.Dep3.md b/test/generators/markdown/Ocamlary.Dep3.md new file mode 100644 index 0000000000..c4d518ccf8 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep3.md @@ -0,0 +1,9 @@ +Ocamlary + +Dep3 + +Module Ocamlary.Dep3 + + + +###### type a \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.X.md b/test/generators/markdown/Ocamlary.Dep4.X.md new file mode 100644 index 0000000000..ecee81f307 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep4.X.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep4 + +X + +Module Dep4.X + + + +###### type b \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.md b/test/generators/markdown/Ocamlary.Dep4.md new file mode 100644 index 0000000000..2468d3a333 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep4.md @@ -0,0 +1,17 @@ +Ocamlary + +Dep4 + +Module Ocamlary.Dep4 + + + +###### module type [T](Ocamlary.Dep4.module-type-T.md) + + + +###### module type [S](Ocamlary.Dep4.module-type-S.md) + + + +###### module [X](Ocamlary.Dep4.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md new file mode 100644 index 0000000000..9aa42c078e --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep4 + +S + +X + +Module S.X + + + +###### type b \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md new file mode 100644 index 0000000000..b3829b6343 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md @@ -0,0 +1,9 @@ +Ocamlary + +Dep4 + +S + +Y + +Module S.Y \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md new file mode 100644 index 0000000000..256e735650 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md @@ -0,0 +1,15 @@ +Ocamlary + +Dep4 + +S + +Module type Dep4.S + + + +###### module [X](Ocamlary.Dep4.module-type-S.X.md) + + + +###### module [Y](Ocamlary.Dep4.module-type-S.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-T.md b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md new file mode 100644 index 0000000000..63dc0895bb --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep4 + +T + +Module type Dep4.T + + + +###### type b \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep5.Z.md b/test/generators/markdown/Ocamlary.Dep5.Z.md new file mode 100644 index 0000000000..23f6e00b9e --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep5.Z.md @@ -0,0 +1,20 @@ +Ocamlary + +Dep5 + +Z + +Module Dep5.Z + + + +###### module X : + +> [Arg.T](Ocamlary.Dep5.argument-1-Arg.md#module-type-T) + + + + +###### module Y = + +> [Dep3](Ocamlary.Dep3.md) diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md new file mode 100644 index 0000000000..44f3ffe5c2 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md @@ -0,0 +1,21 @@ +Ocamlary + +Dep5 + +1-Arg + +Parameter Dep5.1-Arg + + + +###### module type T + + + +###### module type [S](Ocamlary.Dep5.argument-1-Arg.module-type-S.md) + + + +###### module X : + +> [T](#module-type-T) diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md new file mode 100644 index 0000000000..5253ca7eb9 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep5 + +1-Arg + +S + +Y + +Module S.Y \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md new file mode 100644 index 0000000000..a8762bb080 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md @@ -0,0 +1,20 @@ +Ocamlary + +Dep5 + +1-Arg + +S + +Module type 1-Arg.S + + + +###### module X : + +> [T](Ocamlary.Dep5.argument-1-Arg.md#module-type-T) + + + + +###### module [Y](Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep5.md b/test/generators/markdown/Ocamlary.Dep5.md new file mode 100644 index 0000000000..623ed61601 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep5.md @@ -0,0 +1,17 @@ +Ocamlary + +Dep5 + +Module Ocamlary.Dep5 + +# Parameters + + + +###### module [Arg](Ocamlary.Dep5.argument-1-Arg.md) + +# Signature + + + +###### module [Z](Ocamlary.Dep5.Z.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep6.X.Y.md b/test/generators/markdown/Ocamlary.Dep6.X.Y.md new file mode 100644 index 0000000000..8922e5decb --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep6.X.Y.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep6 + +X + +Y + +Module X.Y + + + +###### type d \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep6.X.md b/test/generators/markdown/Ocamlary.Dep6.X.md new file mode 100644 index 0000000000..7cd7db9fb3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep6.X.md @@ -0,0 +1,18 @@ +Ocamlary + +Dep6 + +X + +Module Dep6.X + + + +###### module type R = + +> [S](Ocamlary.Dep6.module-type-S.md) + + + + +###### module [Y](Ocamlary.Dep6.X.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep6.md b/test/generators/markdown/Ocamlary.Dep6.md new file mode 100644 index 0000000000..775bfad917 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep6.md @@ -0,0 +1,17 @@ +Ocamlary + +Dep6 + +Module Ocamlary.Dep6 + + + +###### module type [S](Ocamlary.Dep6.module-type-S.md) + + + +###### module type [T](Ocamlary.Dep6.module-type-T.md) + + + +###### module [X](Ocamlary.Dep6.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-S.md b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md new file mode 100644 index 0000000000..d7afe17198 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep6 + +S + +Module type Dep6.S + + + +###### type d \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md new file mode 100644 index 0000000000..4de9efa353 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md @@ -0,0 +1,13 @@ +Ocamlary + +Dep6 + +T + +Y + +Module T.Y + + + +###### type d \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-T.md b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md new file mode 100644 index 0000000000..a811d8ca99 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md @@ -0,0 +1,18 @@ +Ocamlary + +Dep6 + +T + +Module type Dep6.T + + + +###### module type R = + +> [S](Ocamlary.Dep6.module-type-S.md) + + + + +###### module [Y](Ocamlary.Dep6.module-type-T.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep7.M.md b/test/generators/markdown/Ocamlary.Dep7.M.md new file mode 100644 index 0000000000..f402995f3a --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep7.M.md @@ -0,0 +1,20 @@ +Ocamlary + +Dep7 + +M + +Module Dep7.M + + + +###### module type R = + +> [Arg.S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) + + + + +###### module Y : + +> [R](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md new file mode 100644 index 0000000000..69b47295be --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md @@ -0,0 +1,22 @@ +Ocamlary + +Dep7 + +1-Arg + +X + +Module 1-Arg.X + + + +###### module type R = + +> [S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) + + + + +###### module Y : + +> [R](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md new file mode 100644 index 0000000000..1599ed9b6e --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md @@ -0,0 +1,19 @@ +Ocamlary + +Dep7 + +1-Arg + +Parameter Dep7.1-Arg + + + +###### module type S + + + +###### module type [T](Ocamlary.Dep7.argument-1-Arg.module-type-T.md) + + + +###### module [X](Ocamlary.Dep7.argument-1-Arg.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md new file mode 100644 index 0000000000..6767e2cbcd --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md @@ -0,0 +1,22 @@ +Ocamlary + +Dep7 + +1-Arg + +T + +Module type 1-Arg.T + + + +###### module type R = + +> [S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) + + + + +###### module Y : + +> [R](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.Dep7.md b/test/generators/markdown/Ocamlary.Dep7.md new file mode 100644 index 0000000000..62eff030e6 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep7.md @@ -0,0 +1,17 @@ +Ocamlary + +Dep7 + +Module Ocamlary.Dep7 + +# Parameters + + + +###### module [Arg](Ocamlary.Dep7.argument-1-Arg.md) + +# Signature + + + +###### module [M](Ocamlary.Dep7.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep8.md b/test/generators/markdown/Ocamlary.Dep8.md new file mode 100644 index 0000000000..a4e2a4d7aa --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep8.md @@ -0,0 +1,9 @@ +Ocamlary + +Dep8 + +Module Ocamlary.Dep8 + + + +###### module type [T](Ocamlary.Dep8.module-type-T.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep8.module-type-T.md b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md new file mode 100644 index 0000000000..73d02b2e63 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep8 + +T + +Module type Dep8.T + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md new file mode 100644 index 0000000000..0c8256fdc2 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep9 + +1-X + +Parameter Dep9.1-X + + + +###### module type T \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep9.md b/test/generators/markdown/Ocamlary.Dep9.md new file mode 100644 index 0000000000..9d83e8e7da --- /dev/null +++ b/test/generators/markdown/Ocamlary.Dep9.md @@ -0,0 +1,19 @@ +Ocamlary + +Dep9 + +Module Ocamlary.Dep9 + +# Parameters + + + +###### module [X](Ocamlary.Dep9.argument-1-X.md) + +# Signature + + + +###### module type T = + +> [X.T](Ocamlary.Dep9.argument-1-X.md#module-type-T) diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md new file mode 100644 index 0000000000..90b4535241 --- /dev/null +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md @@ -0,0 +1,11 @@ +Ocamlary + +DoubleInclude1 + +DoubleInclude2 + +Module DoubleInclude1.DoubleInclude2 + + + +###### type double_include \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.md b/test/generators/markdown/Ocamlary.DoubleInclude1.md new file mode 100644 index 0000000000..2cf4fc8739 --- /dev/null +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.md @@ -0,0 +1,9 @@ +Ocamlary + +DoubleInclude1 + +Module Ocamlary.DoubleInclude1 + + + +###### module [DoubleInclude2](Ocamlary.DoubleInclude1.DoubleInclude2.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md new file mode 100644 index 0000000000..7feb228ffd --- /dev/null +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md @@ -0,0 +1,11 @@ +Ocamlary + +DoubleInclude3 + +DoubleInclude2 + +Module DoubleInclude3.DoubleInclude2 + + + +###### type double_include \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.md b/test/generators/markdown/Ocamlary.DoubleInclude3.md new file mode 100644 index 0000000000..b73bb98157 --- /dev/null +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.md @@ -0,0 +1,9 @@ +Ocamlary + +DoubleInclude3 + +Module Ocamlary.DoubleInclude3 + + + +###### module [DoubleInclude2](Ocamlary.DoubleInclude3.DoubleInclude2.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Empty.md b/test/generators/markdown/Ocamlary.Empty.md new file mode 100644 index 0000000000..dbd3e2ae87 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Empty.md @@ -0,0 +1,9 @@ +Ocamlary + +Empty + +Module Ocamlary.Empty + +A plain, empty module + +This module has a signature without any members. \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md new file mode 100644 index 0000000000..3db554831e --- /dev/null +++ b/test/generators/markdown/Ocamlary.ExtMod.md @@ -0,0 +1,20 @@ +Ocamlary + +ExtMod + +Module Ocamlary.ExtMod + + + +###### type t = + +> .. + + + + +###### type [t](#type-t) += + + + +######    | Leisureforce \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..18abdde669 --- /dev/null +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,22 @@ +Ocamlary + +FunctorTypeOf + +1-Collection + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md new file mode 100644 index 0000000000..d171368bc7 --- /dev/null +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -0,0 +1,32 @@ +Ocamlary + +FunctorTypeOf + +1-Collection + +InnerModuleA + +Module 1-Collection.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..2d5a9488f3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,22 @@ +Ocamlary + +FunctorTypeOf + +1-Collection + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md new file mode 100644 index 0000000000..9a45809591 --- /dev/null +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -0,0 +1,34 @@ +Ocamlary + +FunctorTypeOf + +1-Collection + +Parameter FunctorTypeOf.1-Collection + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md new file mode 100644 index 0000000000..0574b2cae0 --- /dev/null +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md @@ -0,0 +1,24 @@ +Ocamlary + +FunctorTypeOf + +Module Ocamlary.FunctorTypeOf + +This comment is for FunctorTypeOf . + +# Parameters + + + +###### module [Collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md) + +# Signature + + + +###### type t = + +> [Collection.collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md new file mode 100644 index 0000000000..43753b9f79 --- /dev/null +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md @@ -0,0 +1,7 @@ +Ocamlary + +IncludeInclude1 + +IncludeInclude2_M + +Module IncludeInclude1.IncludeInclude2_M \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md new file mode 100644 index 0000000000..45b5e251c5 --- /dev/null +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -0,0 +1,13 @@ +Ocamlary + +IncludeInclude1 + +Module Ocamlary.IncludeInclude1 + + + +###### module type [IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) + + + +###### module [IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md new file mode 100644 index 0000000000..c20838d37e --- /dev/null +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md @@ -0,0 +1,11 @@ +Ocamlary + +IncludeInclude1 + +IncludeInclude2 + +Module type IncludeInclude1.IncludeInclude2 + + + +###### type include_include \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md new file mode 100644 index 0000000000..a48c6d18ce --- /dev/null +++ b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md @@ -0,0 +1,5 @@ +Ocamlary + +IncludeInclude2_M + +Module Ocamlary.IncludeInclude2_M \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludedA.md b/test/generators/markdown/Ocamlary.IncludedA.md new file mode 100644 index 0000000000..6f794c6a70 --- /dev/null +++ b/test/generators/markdown/Ocamlary.IncludedA.md @@ -0,0 +1,9 @@ +Ocamlary + +IncludedA + +Module Ocamlary.IncludedA + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.M.md b/test/generators/markdown/Ocamlary.M.md new file mode 100644 index 0000000000..1aa0479608 --- /dev/null +++ b/test/generators/markdown/Ocamlary.M.md @@ -0,0 +1,9 @@ +Ocamlary + +M + +Module Ocamlary.M + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md new file mode 100644 index 0000000000..d5f31458c5 --- /dev/null +++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md @@ -0,0 +1,7 @@ +Ocamlary + +ModuleWithSignature + +Module Ocamlary.ModuleWithSignature + +A plain module of a signature of [EmptySig](Ocamlary.module-type-EmptySig.md) (reference) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md new file mode 100644 index 0000000000..e4194270d4 --- /dev/null +++ b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md @@ -0,0 +1,9 @@ +Ocamlary + +ModuleWithSignatureAlias + +Module Ocamlary.ModuleWithSignatureAlias + +A plain module with an alias signature + +@deprecated: \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.One.md b/test/generators/markdown/Ocamlary.One.md new file mode 100644 index 0000000000..28d023ceab --- /dev/null +++ b/test/generators/markdown/Ocamlary.One.md @@ -0,0 +1,9 @@ +Ocamlary + +One + +Module Ocamlary.One + + + +###### type one \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Only_a_module.md b/test/generators/markdown/Ocamlary.Only_a_module.md new file mode 100644 index 0000000000..26f8ca3170 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Only_a_module.md @@ -0,0 +1,9 @@ +Ocamlary + +Only_a_module + +Module Ocamlary.Only_a_module + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..6d17d441a7 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,20 @@ +Ocamlary + +Recollection + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md new file mode 100644 index 0000000000..417bcba684 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -0,0 +1,30 @@ +Ocamlary + +Recollection + +InnerModuleA + +Module Recollection.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.Recollection.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..9a592a26e2 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,20 @@ +Ocamlary + +Recollection + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..85e838fea5 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,22 @@ +Ocamlary + +Recollection + +1-C + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md new file mode 100644 index 0000000000..caa22b50f6 --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -0,0 +1,32 @@ +Ocamlary + +Recollection + +1-C + +InnerModuleA + +Module 1-C.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.Recollection.argument-1-C.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..ad7c1a59aa --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,22 @@ +Ocamlary + +Recollection + +1-C + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md new file mode 100644 index 0000000000..39c226bc3d --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -0,0 +1,34 @@ +Ocamlary + +Recollection + +1-C + +Parameter Recollection.1-C + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md new file mode 100644 index 0000000000..9438cde94b --- /dev/null +++ b/test/generators/markdown/Ocamlary.Recollection.md @@ -0,0 +1,46 @@ +Ocamlary + +Recollection + +Module Ocamlary.Recollection + +# Parameters + + + +###### module [C](Ocamlary.Recollection.argument-1-C.md) + +# Signature + +This comment is for CollectionModule . + + + +###### type collection = + +> [C.element](Ocamlary.Recollection.argument-1-C.md#type-element) list + + +This comment is for `collection` + + + +###### type element = + +> [C.collection](Ocamlary.Recollection.argument-1-C.md#type-collection) + + + + +###### module [InnerModuleA](Ocamlary.Recollection.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With10.md b/test/generators/markdown/Ocamlary.With10.md new file mode 100644 index 0000000000..a73e8696bb --- /dev/null +++ b/test/generators/markdown/Ocamlary.With10.md @@ -0,0 +1,10 @@ +Ocamlary + +With10 + +Module Ocamlary.With10 + + + +###### module type [T](Ocamlary.With10.module-type-T.md) + diff --git a/test/generators/markdown/Ocamlary.With10.module-type-T.M.md b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md new file mode 100644 index 0000000000..2cb0c59d24 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md @@ -0,0 +1,13 @@ +Ocamlary + +With10 + +T + +M + +Module T.M + + + +###### module type S \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With10.module-type-T.md b/test/generators/markdown/Ocamlary.With10.module-type-T.md new file mode 100644 index 0000000000..2cf73cf727 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With10.module-type-T.md @@ -0,0 +1,19 @@ +Ocamlary + +With10 + +T + +Module type With10.T + +[With10.T]() is a submodule type. + + + +###### module [M](Ocamlary.With10.module-type-T.M.md) + + + +###### module N : + +> [M.S](Ocamlary.With10.module-type-T.M.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.With2.md b/test/generators/markdown/Ocamlary.With2.md new file mode 100644 index 0000000000..9613440ceb --- /dev/null +++ b/test/generators/markdown/Ocamlary.With2.md @@ -0,0 +1,9 @@ +Ocamlary + +With2 + +Module Ocamlary.With2 + + + +###### module type [S](Ocamlary.With2.module-type-S.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With2.module-type-S.md b/test/generators/markdown/Ocamlary.With2.module-type-S.md new file mode 100644 index 0000000000..d6bf61978b --- /dev/null +++ b/test/generators/markdown/Ocamlary.With2.module-type-S.md @@ -0,0 +1,11 @@ +Ocamlary + +With2 + +S + +Module type With2.S + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With3.N.md b/test/generators/markdown/Ocamlary.With3.N.md new file mode 100644 index 0000000000..2676d57b2d --- /dev/null +++ b/test/generators/markdown/Ocamlary.With3.N.md @@ -0,0 +1,11 @@ +Ocamlary + +With3 + +N + +Module With3.N + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With3.md b/test/generators/markdown/Ocamlary.With3.md new file mode 100644 index 0000000000..c427e59fe3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With3.md @@ -0,0 +1,16 @@ +Ocamlary + +With3 + +Module Ocamlary.With3 + + + +###### module M = + +> [With2](Ocamlary.With2.md) + + + + +###### module [N](Ocamlary.With3.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With4.N.md b/test/generators/markdown/Ocamlary.With4.N.md new file mode 100644 index 0000000000..436d5db654 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With4.N.md @@ -0,0 +1,11 @@ +Ocamlary + +With4 + +N + +Module With4.N + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With4.md b/test/generators/markdown/Ocamlary.With4.md new file mode 100644 index 0000000000..a087fca5c0 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With4.md @@ -0,0 +1,9 @@ +Ocamlary + +With4 + +Module Ocamlary.With4 + + + +###### module [N](Ocamlary.With4.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With5.N.md b/test/generators/markdown/Ocamlary.With5.N.md new file mode 100644 index 0000000000..92e61b553e --- /dev/null +++ b/test/generators/markdown/Ocamlary.With5.N.md @@ -0,0 +1,11 @@ +Ocamlary + +With5 + +N + +Module With5.N + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With5.md b/test/generators/markdown/Ocamlary.With5.md new file mode 100644 index 0000000000..b2850b6a21 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With5.md @@ -0,0 +1,13 @@ +Ocamlary + +With5 + +Module Ocamlary.With5 + + + +###### module type [S](Ocamlary.With5.module-type-S.md) + + + +###### module [N](Ocamlary.With5.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With5.module-type-S.md b/test/generators/markdown/Ocamlary.With5.module-type-S.md new file mode 100644 index 0000000000..3c7746f9f5 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With5.module-type-S.md @@ -0,0 +1,11 @@ +Ocamlary + +With5 + +S + +Module type With5.S + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With6.md b/test/generators/markdown/Ocamlary.With6.md new file mode 100644 index 0000000000..c0f3f14627 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With6.md @@ -0,0 +1,9 @@ +Ocamlary + +With6 + +Module Ocamlary.With6 + + + +###### module type [T](Ocamlary.With6.module-type-T.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With6.module-type-T.M.md b/test/generators/markdown/Ocamlary.With6.module-type-T.M.md new file mode 100644 index 0000000000..42ec1ce89b --- /dev/null +++ b/test/generators/markdown/Ocamlary.With6.module-type-T.M.md @@ -0,0 +1,19 @@ +Ocamlary + +With6 + +T + +M + +Module T.M + + + +###### module type S + + + +###### module N : + +> [S](#module-type-S) diff --git a/test/generators/markdown/Ocamlary.With6.module-type-T.md b/test/generators/markdown/Ocamlary.With6.module-type-T.md new file mode 100644 index 0000000000..efaa2742eb --- /dev/null +++ b/test/generators/markdown/Ocamlary.With6.module-type-T.md @@ -0,0 +1,11 @@ +Ocamlary + +With6 + +T + +Module type With6.T + + + +###### module [M](Ocamlary.With6.module-type-T.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With7.argument-1-X.md b/test/generators/markdown/Ocamlary.With7.argument-1-X.md new file mode 100644 index 0000000000..127791ee26 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With7.argument-1-X.md @@ -0,0 +1,11 @@ +Ocamlary + +With7 + +1-X + +Parameter With7.1-X + + + +###### module type T \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With7.md b/test/generators/markdown/Ocamlary.With7.md new file mode 100644 index 0000000000..ff77dec191 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With7.md @@ -0,0 +1,19 @@ +Ocamlary + +With7 + +Module Ocamlary.With7 + +# Parameters + + + +###### module [X](Ocamlary.With7.argument-1-X.md) + +# Signature + + + +###### module type T = + +> [X.T](Ocamlary.With7.argument-1-X.md#module-type-T) diff --git a/test/generators/markdown/Ocamlary.With9.md b/test/generators/markdown/Ocamlary.With9.md new file mode 100644 index 0000000000..a9fd24a946 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With9.md @@ -0,0 +1,9 @@ +Ocamlary + +With9 + +Module Ocamlary.With9 + + + +###### module type [S](Ocamlary.With9.module-type-S.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With9.module-type-S.md b/test/generators/markdown/Ocamlary.With9.module-type-S.md new file mode 100644 index 0000000000..37661fa885 --- /dev/null +++ b/test/generators/markdown/Ocamlary.With9.module-type-S.md @@ -0,0 +1,11 @@ +Ocamlary + +With9 + +S + +Module type With9.S + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.empty_class.md b/test/generators/markdown/Ocamlary.empty_class.md new file mode 100644 index 0000000000..b9d8c41c91 --- /dev/null +++ b/test/generators/markdown/Ocamlary.empty_class.md @@ -0,0 +1,5 @@ +Ocamlary + +empty_class + +Class Ocamlary.empty_class \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md new file mode 100644 index 0000000000..c275f3737b --- /dev/null +++ b/test/generators/markdown/Ocamlary.md @@ -0,0 +1,1362 @@ +Ocamlary + +Module Ocamlary + +This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: + +- comment formatting + +- unassociated comments + +- documentation sections + +- module system documentation including + + 1. submodules + + 2. module aliases + + 3. module types + + 4. module type aliases + + 5. modules with signatures + + 6. modules with aliased signatures + +A numbered list: + +1. 3 + +2. 2 + +3. 1 + +David Sheets is the author. + +@author: David Sheets + +You may find more information about this HTML documentation renderer at [github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary) . + +This is some verbatim text: + +``` +verbatim +``` + +This is some verbatim text: + +``` +[][df[]]}} +``` + +Here is some raw LaTeX: $e^{i\pi} = -1$ + +Here is an index table of Empty modules: + +@[Empty](Ocamlary.Empty.md): A plain, empty module + +@[EmptyAlias](Ocamlary.Empty.md): A plain module alias of Empty + +Odoc doesn't support {!indexlist} . + +Here is some superscript: x 2 + +Here is some subscript: x 0 + +Here are some escaped brackets: { [ @ ] } + +Here is some _emphasis_ followed by code . + +An unassociated comment + +# Level 1 + +## Level 2 + +--- + +### Level 3 + +--- + +#### Level 4 + +--- + +### Basic module stuff + +--- + + + +###### module [Empty](Ocamlary.Empty.md) + +A plain, empty module + + + +###### module type [Empty](Ocamlary.module-type-Empty.md) + +An ambiguous, misnamed module type + + + +###### module type [MissingComment](Ocamlary.module-type-MissingComment.md) + +An ambiguous, misnamed module type + +# Section 9000 + + + +###### module EmptyAlias = + +> [Empty](Ocamlary.Empty.md) + + +A plain module alias of `Empty` + +### EmptySig + +--- + + + +###### module type [EmptySig](Ocamlary.module-type-EmptySig.md) + +A plain, empty module signature + + + +###### module type EmptySigAlias = + +> [EmptySig](Ocamlary.module-type-EmptySig.md) + + +A plain, empty module signature alias of + + + +###### module [ModuleWithSignature](Ocamlary.ModuleWithSignature.md) + +A plain module of a signature of + + + +###### module [ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) + +A plain module with an alias signature + + + +###### module [One](Ocamlary.One.md) + + + +###### module type [SigForMod](Ocamlary.module-type-SigForMod.md) + +There's a signature in a module in this signature. + + + +###### module type [SuperSig](Ocamlary.module-type-SuperSig.md) + +For a good time, see [subSig](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or [subSig](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or [SuperSig.EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) . Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is the section and [EmptySig](Ocamlary.module-type-EmptySig.md) is the module signature. + + + +###### module [Buffer](Ocamlary.Buffer.md) + +References are resolved after everything, so `{!Buffer.t}` + +Some text before exception title. + +### Basic exception stuff + +--- + +After exception title. + + + +###### exception Kaboom of unit + +Unary exception constructor + + + +###### exception Kablam of unit * unit + +Binary exception constructor + + + +###### exception Kapow of unit * unit + +Unary exception constructor over binary tuple + + + +###### exception EmptySig + + + + + +###### exception EmptySigAlias + + + +### Basic type and value stuff with advanced doc comments + +--- + + + +###### type ('a, 'b) a_function = + +> 'a -> 'b + + + + + + +###### val a_function : + +> x : int -> int + + +This is `a_function` + + + +###### val fun_fun_fun : + +> ( ( int , int ) [a_function](#type-a_function) , ( unit , unit ) [a_function](#type-a_function) ) [a_function](#type-a_function) + + + + +###### val fun_maybe : + +> ? yes : unit -> unit -> int + + + + +###### val not_found : + +> unit -> unit + + + + + + +###### val ocaml_org : + +> string + + + + + + +###### val some_file : + +> string + + + + + + +###### val some_doc : + +> string + + + + + + +###### val since_mesozoic : + +> unit + + +This value was introduced in the Mesozoic era. + + + +###### val changing : + +> unit + + +This value has had changes in 1.0.0, 1.1.0, and 1.2.0. + +### Some Operators + +--- + + + +###### val (~-) : + +> unit + + + + +###### val (!) : + +> unit + + + + +###### val (@) : + +> unit + + + + +###### val ($) : + +> unit + + + + +###### val (%) : + +> unit + + + + +###### val (&) : + +> unit + + + + +###### val (*) : + +> unit + + + + +###### val (-) : + +> unit + + + + +###### val (+) : + +> unit + + + + +###### val (-?) : + +> unit + + + + +###### val (/) : + +> unit + + + + +###### val (:=) : + +> unit + + + + +###### val (=) : + +> unit + + + + +###### val (land) : + +> unit + + +### Advanced Module Stuff + +--- + + + +###### module [CollectionModule](Ocamlary.CollectionModule.md) + +This comment is for `CollectionModule` + + + +###### module type [COLLECTION](Ocamlary.module-type-COLLECTION.md) + +module type of + + + +###### module [Recollection](Ocamlary.Recollection.md) + + + +###### module type [MMM](Ocamlary.module-type-MMM.md) + + + +###### module type [RECOLLECTION](Ocamlary.module-type-RECOLLECTION.md) + + + +###### module type [RecollectionModule](Ocamlary.module-type-RecollectionModule.md) + + + +###### module type [A](Ocamlary.module-type-A.md) + + + +###### module type [B](Ocamlary.module-type-B.md) + + + +###### module type [C](Ocamlary.module-type-C.md) + +This module type includes two signatures. + + + +###### module [FunctorTypeOf](Ocamlary.FunctorTypeOf.md) + +This comment is for `FunctorTypeOf` + + + +###### module type [IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) + +This comment is for `IncludeModuleType` + + + +###### module type [ToInclude](Ocamlary.module-type-ToInclude.md) + + + +###### module [IncludedA](Ocamlary.IncludedA.md) + + + +###### module type [IncludedB](Ocamlary.module-type-IncludedB.md) + +### Advanced Type Stuff + +--- + + + +###### type record = { + + + +######    field1 : int ; + +This comment is for `field1` + + + +######    field2 : int ; + +This comment is for `field2` + +} + +This comment is for `record`This comment is also for `record` + + + +###### type mutable_record = { + + + +######    mutable a : int ; + +`a` + + + +######    b : unit ; + +`b` + + + +######    mutable c : int ; + +`c` + +} + + + +###### type universe_record = { + + + +######    nihilate : 'a. 'a -> unit ; + +} + + + +###### type variant = + + + +######    | TagA + +This comment is for `TagA` + + + +######    | ConstrB of int + +This comment is for `ConstrB` + + + +######    | ConstrC of int * int + +This comment is for binary `ConstrC` + + + +######    | ConstrD of int * int + +This comment is for unary `ConstrD` + +This comment is for `variant`This comment is also for `variant` + + + +###### type poly_variant = [ + + + +######    | `TagA + + + +######    | `ConstrB of int + +] + +This comment is for `poly_variant`Wow! It was a polymorphic variant! + + + +###### type (_, _) full_gadt = + + + +######    | Tag : ( unit , unit ) [full_gadt](#type-full_gadt) + + + +######    | First : 'a -> + + + +######    | Second : 'a -> + + + +######    | Exist : 'a * 'b -> + +This comment is for `full_gadt`Wow! It was a GADT! + + + +###### type 'a partial_gadt = + + + +######    | AscribeTag : 'a [partial_gadt](#type-partial_gadt) + + + +######    | OfTag of 'a [partial_gadt](#type-partial_gadt) + + + +######    | ExistGadtTag : ( 'a -> 'b ) -> + +This comment is for `partial_gadt`Wow! It was a mixed GADT! + + + +###### type alias = + +> [variant](#type-variant) + + +This comment is for `alias` + + + +###### type tuple = + +> ( [alias](#type-alias) * [alias](#type-alias) ) * [alias](#type-alias) * ( [alias](#type-alias) * [alias](#type-alias) ) + + +This comment is for `tuple` + + + +###### type variant_alias = [variant](#type-variant) = + + + +######    | TagA + + + +######    | ConstrB of int + + + +######    | ConstrC of int * int + + + +######    | ConstrD of int * int + +This comment is for `variant_alias` + + + +###### type record_alias = [record](#type-record) = { + + + +######    field1 : int ; + + + +######    field2 : int ; + +} + +This comment is for `record_alias` + + + +###### type poly_variant_union = [ + + + +######    | [poly_variant](#type-poly_variant) + + + +######    | `TagC + +] + +This comment is for `poly_variant_union` + + + +###### type 'a poly_poly_variant = [ + + + +######    | `TagA of 'a + +] + + + +###### type ('a, 'b) bin_poly_poly_variant = [ + + + +######    | `TagA of 'a + + + +######    | `ConstrB of 'b + +] + + + +###### type 'a open_poly_variant = + +> [> `TagA ] as ' a + + + + +###### type 'a open_poly_variant2 = + +> [> `ConstrB of int ] as ' a + + + + +###### type 'a open_poly_variant_alias = + +> 'a [open_poly_variant](#type-open_poly_variant) [open_poly_variant2](#type-open_poly_variant2) + + + + +###### type 'a poly_fun = + +> [> `ConstrB of int ] as ' a -> 'a + + + + +###### type 'a poly_fun_constraint = + +> 'a -> 'a constraint 'a = [> `TagA ] + + + + +###### type 'a closed_poly_variant = + +> [< `One | `Two ] as ' a + + + + +###### type 'a clopen_poly_variant = + +> [< `One | `Two of int | `Three Two Three ] as ' a + + + + +###### type nested_poly_variant = [ + + + +######    | `A + + + +######    | `B of [ `B1 | `B2 ] + + + +######    | `C + + + +######    | `D of [ `D1 of [ `D1a ] ] + +] + + + +###### type ('a, 'b) full_gadt_alias = ( 'a , 'b ) [full_gadt](#type-full_gadt) = + + + +######    | Tag : ( unit , unit ) [full_gadt_alias](#type-full_gadt_alias) + + + +######    | First : 'a -> + + + +######    | Second : 'a -> + + + +######    | Exist : 'a * 'b -> + +This comment is for `full_gadt_alias` + + + +###### type 'a partial_gadt_alias = 'a [partial_gadt](#type-partial_gadt) = + + + +######    | AscribeTag : 'a [partial_gadt_alias](#type-partial_gadt_alias) + + + +######    | OfTag of 'a [partial_gadt_alias](#type-partial_gadt_alias) + + + +######    | ExistGadtTag : ( 'a -> 'b ) -> + +This comment is for `partial_gadt_alias` + + + +###### exception Exn_arrow : + +> unit -> + + +This comment is for + + + +###### type mutual_constr_a = + + + +######    | A + + + +######    | B_ish of [mutual_constr_b](#type-mutual_constr_b) + +This comment is between + +This comment is for + + + +###### and mutual_constr_b = + + + +######    | B + + + +######    | A_ish of [mutual_constr_a](#type-mutual_constr_a) + +This comment must be here for the next to associate correctly. + +This comment is for + + + +###### type rec_obj = + +> < f : int ; g : unit -> unit ; h : [rec_obj](#type-rec_obj) > + + + + +###### type 'a open_obj = + +> < f : int ; g : unit -> unit .. > as ' a + + + + +###### type 'a oof = + +> < a : unit .. > as ' a -> 'a + + + + +###### type 'a any_obj = + +> < .. > as ' a + + + + +###### type empty_obj = + +> < > + + + + +###### type one_meth = + +> < meth : unit > + + + + +###### type ext = + +> .. + + +A mystery wrapped in an ellipsis + + + +###### type [ext](#type-ext) += + + + +######    | ExtA + + + +###### type [ext](#type-ext) += + + + +######    | ExtB + + + +###### type [ext](#type-ext) += + + + +######    | ExtC of unit + + + +######    | ExtD of [ext](#type-ext) + + + +###### type [ext](#type-ext) += + + + +######    | ExtE + + + +###### type [ext](#type-ext) += + + + +######    | ExtF + + + +###### type 'a poly_ext = + +> .. + + +'a poly_ext + + + +###### type [poly_ext](#type-poly_ext) += + + + +######    | Foo of 'b + + + +######    | Bar of 'b * 'b + +'b poly_ext + + + +###### type [poly_ext](#type-poly_ext) += + + + +######    | Quux of 'c + +'c poly_ext + + + +###### module [ExtMod](Ocamlary.ExtMod.md) + + + +###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += + + + +######    | ZzzTop0 + +It's got the rock + + + +###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += + + + +######    | ZzzTop of unit + +and it packs a unit. + + + +###### val launch_missiles : + +> unit -> unit + + +Rotate keys on my mark... + + + +###### type my_mod = + +> ( module [COLLECTION](Ocamlary.module-type-COLLECTION.md) ) + + +A brown paper package tied up with string + + + +###### class [empty_class](Ocamlary.empty_class.md) + + + +###### class [one_method_class](Ocamlary.one_method_class.md) + + + +###### class [two_method_class](Ocamlary.two_method_class.md) + + + +###### class 'a [param_class](Ocamlary.param_class.md) + + + +###### type my_unit_object = + +> unit [param_class](Ocamlary.param_class.md) + + + + +###### type 'a my_unit_class = + +> unit param_class as ' a + + + + +###### module [Dep1](Ocamlary.Dep1.md) + + + +###### module [Dep2](Ocamlary.Dep2.md) + + + +###### type dep1 = + +> [Dep2(Dep1).B.c](Ocamlary.Dep1.module-type-S.c.md) + + + + +###### module [Dep3](Ocamlary.Dep3.md) + + + +###### module [Dep4](Ocamlary.Dep4.md) + + + +###### module [Dep5](Ocamlary.Dep5.md) + + + +###### type dep2 = + +> [Dep5(Dep4).Z.X.b](Ocamlary.Dep4.module-type-T.md#type-b) + + + + +###### type dep3 = + +> [Dep5(Dep4).Z.Y.a](Ocamlary.Dep3.md#type-a) + + + + +###### module [Dep6](Ocamlary.Dep6.md) + + + +###### module [Dep7](Ocamlary.Dep7.md) + + + +###### type dep4 = + +> [Dep7(Dep6).M.Y.d](Ocamlary.Dep6.module-type-T.Y.md#type-d) + + + + +###### module [Dep8](Ocamlary.Dep8.md) + + + +###### module [Dep9](Ocamlary.Dep9.md) + + + +###### module type [Dep10](Ocamlary.module-type-Dep10.md) + + + +###### module [Dep11](Ocamlary.Dep11.md) + + + +###### module [Dep12](Ocamlary.Dep12.md) + + + +###### module [Dep13](Ocamlary.Dep13.md) + + + +###### type dep5 = + +> [Dep13.c](Ocamlary.Dep13.c.md) + + + + +###### module type [With1](Ocamlary.module-type-With1.md) + + + +###### module [With2](Ocamlary.With2.md) + + + +###### module [With3](Ocamlary.With3.md) + + + +###### type with1 = + +> [With3.N.t](Ocamlary.With3.N.md#type-t) + + + + +###### module [With4](Ocamlary.With4.md) + + + +###### type with2 = + +> [With4.N.t](Ocamlary.With4.N.md#type-t) + + + + +###### module [With5](Ocamlary.With5.md) + + + +###### module [With6](Ocamlary.With6.md) + + + +###### module [With7](Ocamlary.With7.md) + + + +###### module type [With8](Ocamlary.module-type-With8.md) + + + +###### module [With9](Ocamlary.With9.md) + + + +###### module [With10](Ocamlary.With10.md) + + + +###### module type [With11](Ocamlary.module-type-With11.md) + + + +###### module type [NestedInclude1](Ocamlary.module-type-NestedInclude1.md) + + + +###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude2.md) + + + +###### type nested_include = + +> int + + + + +###### module [DoubleInclude1](Ocamlary.DoubleInclude1.md) + + + +###### module [DoubleInclude3](Ocamlary.DoubleInclude3.md) + + + +###### type double_include + + + +###### module [IncludeInclude1](Ocamlary.IncludeInclude1.md) + + + +###### module type [IncludeInclude2](Ocamlary.module-type-IncludeInclude2.md) + + + +###### module [IncludeInclude2_M](Ocamlary.IncludeInclude2_M.md) + + + +###### type include_include + +# Trying the {!modules: ...} command. + +With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references. + +With odoc, everything should be resolved (and linked) but only toplevel units will be documented. + +@[Dep1.X](Ocamlary.Dep1.X.md): + +@[Ocamlary.IncludeInclude1](Ocamlary.IncludeInclude1.md): + +@[Ocamlary](): This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: + +### Weirder usages involving module types + +--- + +@[IncludeInclude1.IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md): + +@[Dep4.X](Ocamlary.Dep4.X.md): + +# Playing with @canonical paths + + + +###### module [CanonicalTest](Ocamlary.CanonicalTest.md) + +Some ref to [CanonicalTest.Base_Tests.C.t](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) and [CanonicalTest.Base_Tests.L.id](Ocamlary.CanonicalTest.Base.List.md#val-id) . But also to [CanonicalTest.Base.List](Ocamlary.CanonicalTest.Base.List.md) and [CanonicalTest.Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) + +# Aliases again + + + +###### module [Aliases](Ocamlary.Aliases.md) + +Let's imitate jst's layout. + +# Section title splicing + +I can refer to + +- {!section:indexmodules} : [Trying the {!modules: ...} command.](#indexmodules) + +- {!aliases} : [Aliases again](#aliases) + +But also to things in submodules: + +- {!section:SuperSig.SubSigA.subSig} : [subSig](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) + +- {!Aliases.incl} : [incl](Ocamlary.Aliases.md#incl) + +And just to make sure we do not mess up: + +- {{!section:indexmodules}A} : [A](#indexmodules) + +- {{!aliases}B} : [B](#aliases) + +- {{!section:SuperSig.SubSigA.subSig}C} : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) + +- {{!Aliases.incl}D} : [D](Ocamlary.Aliases.md#incl) + +# New reference syntax + + + +###### module type [M](Ocamlary.module-type-M.md) + + + +###### module [M](Ocamlary.M.md) + +Here goes: + +- {!module-M.t} : [M.t](Ocamlary.M.md#type-t) + +- {!module-type-M.t} : [M.t](Ocamlary.module-type-M.md#type-t) + + + +###### module [Only_a_module](Ocamlary.Only_a_module.md) + +- {!Only_a_module.t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) + +- {!module-Only_a_module.t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) + +- {!module-Only_a_module.type-t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) + +- {!type:Only_a_module.t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) + + + +###### module type [TypeExt](Ocamlary.module-type-TypeExt.md) + + + +###### type new_t = + +> .. + + + + +###### type [new_t](#type-new_t) += + + + +######    | C + + + +###### module type [TypeExtPruned](Ocamlary.module-type-TypeExtPruned.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..9b892baf6f --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,22 @@ +Ocamlary + +A + +Q + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md new file mode 100644 index 0000000000..593082d1c3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -0,0 +1,32 @@ +Ocamlary + +A + +Q + +InnerModuleA + +Module Q.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.module-type-A.Q.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..4c60aac560 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,22 @@ +Ocamlary + +A + +Q + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.md b/test/generators/markdown/Ocamlary.module-type-A.Q.md new file mode 100644 index 0000000000..ae035a834f --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.md @@ -0,0 +1,34 @@ +Ocamlary + +A + +Q + +Module A.Q + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.module-type-A.Q.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.md b/test/generators/markdown/Ocamlary.module-type-A.md new file mode 100644 index 0000000000..c0dacd95fe --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-A.md @@ -0,0 +1,13 @@ +Ocamlary + +A + +Module type Ocamlary.A + + + +###### type t + + + +###### module [Q](Ocamlary.module-type-A.Q.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..dc4874b532 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,22 @@ +Ocamlary + +B + +Q + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md new file mode 100644 index 0000000000..71ee07169e --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -0,0 +1,32 @@ +Ocamlary + +B + +Q + +InnerModuleA + +Module Q.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.module-type-B.Q.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..4aca417865 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,22 @@ +Ocamlary + +B + +Q + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.md b/test/generators/markdown/Ocamlary.module-type-B.Q.md new file mode 100644 index 0000000000..6c0c5601ee --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.md @@ -0,0 +1,34 @@ +Ocamlary + +B + +Q + +Module B.Q + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.module-type-B.Q.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.md b/test/generators/markdown/Ocamlary.module-type-B.md new file mode 100644 index 0000000000..7e1c0ab058 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-B.md @@ -0,0 +1,13 @@ +Ocamlary + +B + +Module type Ocamlary.B + + + +###### type t + + + +###### module [Q](Ocamlary.module-type-B.Q.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..9c2b069abe --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,22 @@ +Ocamlary + +C + +Q + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md new file mode 100644 index 0000000000..bfc93bae57 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -0,0 +1,32 @@ +Ocamlary + +C + +Q + +InnerModuleA + +Module Q.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.module-type-C.Q.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..e15036d239 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,22 @@ +Ocamlary + +C + +Q + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.md b/test/generators/markdown/Ocamlary.module-type-C.Q.md new file mode 100644 index 0000000000..e33aca87bb --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.md @@ -0,0 +1,34 @@ +Ocamlary + +C + +Q + +Module C.Q + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.module-type-C.Q.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.md b/test/generators/markdown/Ocamlary.module-type-C.md new file mode 100644 index 0000000000..61fd6eff45 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-C.md @@ -0,0 +1,20 @@ +Ocamlary + +C + +Module type Ocamlary.C + +This module type includes two signatures. + +- it includes [A](Ocamlary.module-type-A.md) + +- it includes [B](Ocamlary.module-type-B.md) with some substitution + + + +###### type t + + + +###### module [Q](Ocamlary.module-type-C.Q.md) + diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..9e1dbd7b18 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,20 @@ +Ocamlary + +COLLECTION + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md new file mode 100644 index 0000000000..c57f5ba2e3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -0,0 +1,30 @@ +Ocamlary + +COLLECTION + +InnerModuleA + +Module COLLECTION.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.module-type-COLLECTION.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..dca0a0f4e7 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,20 @@ +Ocamlary + +COLLECTION + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md new file mode 100644 index 0000000000..7b223b9543 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md @@ -0,0 +1,34 @@ +Ocamlary + +COLLECTION + +Module type Ocamlary.COLLECTION + +module type of + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.module-type-COLLECTION.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-Dep10.md b/test/generators/markdown/Ocamlary.module-type-Dep10.md new file mode 100644 index 0000000000..afcdabb14c --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-Dep10.md @@ -0,0 +1,11 @@ +Ocamlary + +Dep10 + +Module type Ocamlary.Dep10 + + + +###### type t = + +> int diff --git a/test/generators/markdown/Ocamlary.module-type-Empty.md b/test/generators/markdown/Ocamlary.module-type-Empty.md new file mode 100644 index 0000000000..ed4eacf2c3 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-Empty.md @@ -0,0 +1,11 @@ +Ocamlary + +Empty + +Module type Ocamlary.Empty + +An ambiguous, misnamed module type + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-EmptySig.md b/test/generators/markdown/Ocamlary.module-type-EmptySig.md new file mode 100644 index 0000000000..1b338cbfbd --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-EmptySig.md @@ -0,0 +1,7 @@ +Ocamlary + +EmptySig + +Module type Ocamlary.EmptySig + +A plain, empty module signature \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md new file mode 100644 index 0000000000..07be07f04e --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md @@ -0,0 +1,9 @@ +Ocamlary + +IncludeInclude2 + +Module type Ocamlary.IncludeInclude2 + + + +###### type include_include \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md new file mode 100644 index 0000000000..b748300913 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md @@ -0,0 +1,8 @@ +Ocamlary + +IncludeModuleType + +Module type Ocamlary.IncludeModuleType + +This comment is for IncludeModuleType . + diff --git a/test/generators/markdown/Ocamlary.module-type-IncludedB.md b/test/generators/markdown/Ocamlary.module-type-IncludedB.md new file mode 100644 index 0000000000..8b1c800db4 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-IncludedB.md @@ -0,0 +1,9 @@ +Ocamlary + +IncludedB + +Module type Ocamlary.IncludedB + + + +###### type s \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-M.md b/test/generators/markdown/Ocamlary.module-type-M.md new file mode 100644 index 0000000000..eb6d8b515a --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-M.md @@ -0,0 +1,9 @@ +Ocamlary + +M + +Module type Ocamlary.M + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..5a4de9a0c8 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,22 @@ +Ocamlary + +MMM + +C + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md new file mode 100644 index 0000000000..aff70d1add --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -0,0 +1,32 @@ +Ocamlary + +MMM + +C + +InnerModuleA + +Module C.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.module-type-MMM.C.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..55463e216d --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,22 @@ +Ocamlary + +MMM + +C + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.md new file mode 100644 index 0000000000..ddb74733cc --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.md @@ -0,0 +1,34 @@ +Ocamlary + +MMM + +C + +Module MMM.C + +This comment is for CollectionModule . + + + +###### type collection + +This comment is for `collection` + + + +###### type element + + + +###### module [InnerModuleA](Ocamlary.module-type-MMM.C.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.md b/test/generators/markdown/Ocamlary.module-type-MMM.md new file mode 100644 index 0000000000..5749774781 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-MMM.md @@ -0,0 +1,9 @@ +Ocamlary + +MMM + +Module type Ocamlary.MMM + + + +###### module [C](Ocamlary.module-type-MMM.C.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MissingComment.md b/test/generators/markdown/Ocamlary.module-type-MissingComment.md new file mode 100644 index 0000000000..2f53953731 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-MissingComment.md @@ -0,0 +1,11 @@ +Ocamlary + +MissingComment + +Module type Ocamlary.MissingComment + +An ambiguous, misnamed module type + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md new file mode 100644 index 0000000000..d44a7d5690 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md @@ -0,0 +1,9 @@ +Ocamlary + +NestedInclude1 + +Module type Ocamlary.NestedInclude1 + + + +###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md new file mode 100644 index 0000000000..2320d51d55 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md @@ -0,0 +1,11 @@ +Ocamlary + +NestedInclude1 + +NestedInclude2 + +Module type NestedInclude1.NestedInclude2 + + + +###### type nested_include \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md new file mode 100644 index 0000000000..f041aa93d1 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md @@ -0,0 +1,9 @@ +Ocamlary + +NestedInclude2 + +Module type Ocamlary.NestedInclude2 + + + +###### type nested_include \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md b/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md new file mode 100644 index 0000000000..c7295401d4 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md @@ -0,0 +1,11 @@ +Ocamlary + +RECOLLECTION + +Module type Ocamlary.RECOLLECTION + + + +###### module C = + +> [Recollection(CollectionModule)](Ocamlary.Recollection.md) diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md new file mode 100644 index 0000000000..9d23a3cbc9 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md @@ -0,0 +1,20 @@ +Ocamlary + +RecollectionModule + +InnerModuleA + +InnerModuleA' + +Module InnerModuleA.InnerModuleA' + +This comment is for InnerModuleA' . + + + +###### type t = + +> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md new file mode 100644 index 0000000000..062efc7d2e --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -0,0 +1,30 @@ +Ocamlary + +RecollectionModule + +InnerModuleA + +Module RecollectionModule.InnerModuleA + +This comment is for InnerModuleA . + + + +###### type t = + +> [collection](Ocamlary.module-type-RecollectionModule.md#type-collection) + + +This comment is for `t` + + + +###### module [InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) + +This comment is for `InnerModuleA'` + + + +###### module type [InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) + +This comment is for `InnerModuleTypeA'` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md new file mode 100644 index 0000000000..bf291e61c6 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -0,0 +1,20 @@ +Ocamlary + +RecollectionModule + +InnerModuleA + +InnerModuleTypeA' + +Module type InnerModuleA.InnerModuleTypeA' + +This comment is for InnerModuleTypeA' . + + + +###### type t = + +> [InnerModuleA'.t](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md#type-t) + + +This comment is for `t` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md new file mode 100644 index 0000000000..f8fc3ce567 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -0,0 +1,34 @@ +Ocamlary + +RecollectionModule + +Module type Ocamlary.RecollectionModule + + + +###### type collection = + +> [CollectionModule.element](Ocamlary.CollectionModule.md#type-element) list + + + + +###### type element = + +> [CollectionModule.collection](Ocamlary.CollectionModule.md#type-collection) + + + + +###### module [InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) + +This comment is for `InnerModuleA` + + + +###### module type InnerModuleTypeA = + +> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) + + +This comment is for `InnerModuleTypeA` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md new file mode 100644 index 0000000000..d6fd1ce584 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md @@ -0,0 +1,11 @@ +Ocamlary + +SigForMod + +Inner + +Module SigForMod.Inner + + + +###### module type [Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md new file mode 100644 index 0000000000..e80f1e82d6 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md @@ -0,0 +1,9 @@ +Ocamlary + +SigForMod + +Inner + +Empty + +Module type Inner.Empty \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.md new file mode 100644 index 0000000000..f585bb4669 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.md @@ -0,0 +1,11 @@ +Ocamlary + +SigForMod + +Module type Ocamlary.SigForMod + +There's a signature in a module in this signature. + + + +###### module [Inner](Ocamlary.module-type-SigForMod.Inner.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.md new file mode 100644 index 0000000000..765d2ee678 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md @@ -0,0 +1,25 @@ +Ocamlary + +SuperSig + +Module type Ocamlary.SuperSig + + + +###### module type [SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) + + + +###### module type [SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) + + + +###### module type [EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) + + + +###### module type [One](Ocamlary.module-type-SuperSig.module-type-One.md) + + + +###### module type [SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md new file mode 100644 index 0000000000..eeec955a78 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md @@ -0,0 +1,11 @@ +Ocamlary + +SuperSig + +EmptySig + +Module type SuperSig.EmptySig + + + +###### type not_actually_empty \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md new file mode 100644 index 0000000000..cd54601f98 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md @@ -0,0 +1,11 @@ +Ocamlary + +SuperSig + +One + +Module type SuperSig.One + + + +###### type two \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md new file mode 100644 index 0000000000..a9b585d699 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md @@ -0,0 +1,13 @@ +Ocamlary + +SuperSig + +SubSigA + +SubSigAMod + +Module SubSigA.SubSigAMod + + + +###### type sub_sig_a_mod \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md new file mode 100644 index 0000000000..bacf3a486d --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -0,0 +1,19 @@ +Ocamlary + +SuperSig + +SubSigA + +Module type SuperSig.SubSigA + +### A Labeled Section Header Inside of a Signature + +--- + + + +###### type t + + + +###### module [SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md new file mode 100644 index 0000000000..ddbfb701df --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md @@ -0,0 +1,15 @@ +Ocamlary + +SuperSig + +SubSigB + +Module type SuperSig.SubSigB + +### Another Labeled Section Header Inside of a Signature + +--- + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md new file mode 100644 index 0000000000..c4692c37c0 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md @@ -0,0 +1,7 @@ +Ocamlary + +SuperSig + +SuperSig + +Module type SuperSig.SuperSig \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md new file mode 100644 index 0000000000..9c3266344e --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md @@ -0,0 +1,11 @@ +Ocamlary + +ToInclude + +IncludedA + +Module ToInclude.IncludedA + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.md new file mode 100644 index 0000000000..a5d59c8810 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md @@ -0,0 +1,13 @@ +Ocamlary + +ToInclude + +Module type Ocamlary.ToInclude + + + +###### module [IncludedA](Ocamlary.module-type-ToInclude.IncludedA.md) + + + +###### module type [IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md new file mode 100644 index 0000000000..c7fd74d8a7 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md @@ -0,0 +1,11 @@ +Ocamlary + +ToInclude + +IncludedB + +Module type ToInclude.IncludedB + + + +###### type s \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExt.md b/test/generators/markdown/Ocamlary.module-type-TypeExt.md new file mode 100644 index 0000000000..94bc50d5b9 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-TypeExt.md @@ -0,0 +1,26 @@ +Ocamlary + +TypeExt + +Module type Ocamlary.TypeExt + + + +###### type t = + +> .. + + + + +###### type [t](#type-t) += + + + +######    | C + + + +###### val f : + +> [t](#type-t) -> unit diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md new file mode 100644 index 0000000000..afa348df42 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md @@ -0,0 +1,19 @@ +Ocamlary + +TypeExtPruned + +Module type Ocamlary.TypeExtPruned + + + +###### type [new_t](Ocamlary.md#type-new_t) += + + + +######    | C + + + +###### val f : + +> [new_t](Ocamlary.md#type-new_t) -> unit diff --git a/test/generators/markdown/Ocamlary.module-type-With1.M.md b/test/generators/markdown/Ocamlary.module-type-With1.M.md new file mode 100644 index 0000000000..08934da2e8 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With1.M.md @@ -0,0 +1,11 @@ +Ocamlary + +With1 + +M + +Module With1.M + + + +###### module type S \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-With1.md b/test/generators/markdown/Ocamlary.module-type-With1.md new file mode 100644 index 0000000000..d69bf3a95f --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With1.md @@ -0,0 +1,15 @@ +Ocamlary + +With1 + +Module type Ocamlary.With1 + + + +###### module [M](Ocamlary.module-type-With1.M.md) + + + +###### module N : + +> [M.S](Ocamlary.module-type-With1.M.md#module-type-S) diff --git a/test/generators/markdown/Ocamlary.module-type-With11.N.md b/test/generators/markdown/Ocamlary.module-type-With11.N.md new file mode 100644 index 0000000000..69989d4ff9 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With11.N.md @@ -0,0 +1,13 @@ +Ocamlary + +With11 + +N + +Module With11.N + + + +###### type t = + +> int diff --git a/test/generators/markdown/Ocamlary.module-type-With11.md b/test/generators/markdown/Ocamlary.module-type-With11.md new file mode 100644 index 0000000000..788a44e30e --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With11.md @@ -0,0 +1,16 @@ +Ocamlary + +With11 + +Module type Ocamlary.With11 + + + +###### module M = + +> [With9](Ocamlary.With9.md) + + + + +###### module [N](Ocamlary.module-type-With11.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-With8.M.N.md b/test/generators/markdown/Ocamlary.module-type-With8.M.N.md new file mode 100644 index 0000000000..719b256b25 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With8.M.N.md @@ -0,0 +1,15 @@ +Ocamlary + +With8 + +M + +N + +Module M.N + + + +###### type t = + +> [With5.N.t](Ocamlary.With5.N.md#type-t) diff --git a/test/generators/markdown/Ocamlary.module-type-With8.M.md b/test/generators/markdown/Ocamlary.module-type-With8.M.md new file mode 100644 index 0000000000..43d67f6a96 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With8.M.md @@ -0,0 +1,18 @@ +Ocamlary + +With8 + +M + +Module With8.M + + + +###### module type S = + +> [With5.S](Ocamlary.With5.module-type-S.md) + + + + +###### module [N](Ocamlary.module-type-With8.M.N.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-With8.md b/test/generators/markdown/Ocamlary.module-type-With8.md new file mode 100644 index 0000000000..c127b51a56 --- /dev/null +++ b/test/generators/markdown/Ocamlary.module-type-With8.md @@ -0,0 +1,9 @@ +Ocamlary + +With8 + +Module type Ocamlary.With8 + + + +###### module [M](Ocamlary.module-type-With8.M.md) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.one_method_class.md b/test/generators/markdown/Ocamlary.one_method_class.md new file mode 100644 index 0000000000..ed0a7a2b02 --- /dev/null +++ b/test/generators/markdown/Ocamlary.one_method_class.md @@ -0,0 +1,11 @@ +Ocamlary + +one_method_class + +Class Ocamlary.one_method_class + + + +###### method go : + +> unit diff --git a/test/generators/markdown/Ocamlary.param_class.md b/test/generators/markdown/Ocamlary.param_class.md new file mode 100644 index 0000000000..c628e846e2 --- /dev/null +++ b/test/generators/markdown/Ocamlary.param_class.md @@ -0,0 +1,11 @@ +Ocamlary + +param_class + +Class Ocamlary.param_class + + + +###### method v : + +> 'a diff --git a/test/generators/markdown/Ocamlary.two_method_class.md b/test/generators/markdown/Ocamlary.two_method_class.md new file mode 100644 index 0000000000..95d7ca1870 --- /dev/null +++ b/test/generators/markdown/Ocamlary.two_method_class.md @@ -0,0 +1,18 @@ +Ocamlary + +two_method_class + +Class Ocamlary.two_method_class + + + +###### method one : + +> [one_method_class](Ocamlary.one_method_class.md) + + + + +###### method undo : + +> unit diff --git a/test/generators/markdown/Recent.X.md b/test/generators/markdown/Recent.X.md new file mode 100644 index 0000000000..43e5518a91 --- /dev/null +++ b/test/generators/markdown/Recent.X.md @@ -0,0 +1,32 @@ +Recent + +X + +Module Recent.X + + + +###### module L := + +> [Z.Y](Recent.Z.Y.md) + + + + +###### type t = + +> int [Z.Y.X.t](Recent.Z.Y.X.md#type-t) + + + + +###### type u := + +> int + + + + +###### type v = + +> [u](#type-u) [Z.Y.X.t](Recent.Z.Y.X.md#type-t) diff --git a/test/generators/markdown/Recent.Z.Y.X.md b/test/generators/markdown/Recent.Z.Y.X.md new file mode 100644 index 0000000000..78ce61b1f3 --- /dev/null +++ b/test/generators/markdown/Recent.Z.Y.X.md @@ -0,0 +1,13 @@ +Recent + +Z + +Y + +X + +Module Y.X + + + +###### type 'a t \ No newline at end of file diff --git a/test/generators/markdown/Recent.Z.Y.md b/test/generators/markdown/Recent.Z.Y.md new file mode 100644 index 0000000000..ae087a1db9 --- /dev/null +++ b/test/generators/markdown/Recent.Z.Y.md @@ -0,0 +1,11 @@ +Recent + +Z + +Y + +Module Z.Y + + + +###### module [X](Recent.Z.Y.X.md) \ No newline at end of file diff --git a/test/generators/markdown/Recent.Z.md b/test/generators/markdown/Recent.Z.md new file mode 100644 index 0000000000..ce353f8c63 --- /dev/null +++ b/test/generators/markdown/Recent.Z.md @@ -0,0 +1,9 @@ +Recent + +Z + +Module Recent.Z + + + +###### module [Y](Recent.Z.Y.md) \ No newline at end of file diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md new file mode 100644 index 0000000000..389ea13229 --- /dev/null +++ b/test/generators/markdown/Recent.md @@ -0,0 +1,151 @@ +Recent + +Module Recent + + + +###### module type [S](Recent.module-type-S.md) + + + +###### module type [S1](Recent.module-type-S1.md) + + + +###### type variant = + + + +######    | A + + + +######    | B of int + + + +######    | C + +foo + + + +######    | D + + + + + +######    | E of { + + + +######    a : int ; + +} + + + +###### type _ gadt = + + + +######    | A : int [gadt](#type-gadt) + + + +######    | B : int -> + +foo + + + +######    | C : { + + + +######    a : int ; + +} -> + + + +###### type polymorphic_variant = [ + + + +######    | `A + + + +######    | `B of int + + + +######    | `C + +foo + + + +######    | `D + +bar + +] + + + +###### type empty_variant = + +> | + + + + +###### type nonrec nonrec_ = + +> int + + + + +###### type empty_conj = + + + +######    | X : [< `X of & 'a & int * float ] -> + + + +###### type conj = + + + +######    | X : [< `X of int & [< `B of int & float ] ] -> + + + +###### val empty_conj : + +> [< `X of & 'a & int * float ] + + + + +###### val conj : + +> [< `X of int & [< `B of int & float ] ] + + + + +###### module [Z](Recent.Z.md) + + + +###### module [X](Recent.X.md) + + + +###### module type [PolyS](Recent.module-type-PolyS.md) \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md new file mode 100644 index 0000000000..482faba3c0 --- /dev/null +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -0,0 +1,19 @@ +Recent + +PolyS + +Module type Recent.PolyS + + + +###### type t = [ + + + +######    | `A + + + +######    | `B + +] \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-S.md b/test/generators/markdown/Recent.module-type-S.md new file mode 100644 index 0000000000..b5379a4ec4 --- /dev/null +++ b/test/generators/markdown/Recent.module-type-S.md @@ -0,0 +1,5 @@ +Recent + +S + +Module type Recent.S \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-S1.argument-1-_.md b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md new file mode 100644 index 0000000000..a976212b40 --- /dev/null +++ b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md @@ -0,0 +1,7 @@ +Recent + +S1 + +1-_ + +Parameter S1.1-_ \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-S1.md b/test/generators/markdown/Recent.module-type-S1.md new file mode 100644 index 0000000000..02edd128d5 --- /dev/null +++ b/test/generators/markdown/Recent.module-type-S1.md @@ -0,0 +1,13 @@ +Recent + +S1 + +Module type Recent.S1 + +# Parameters + + + +###### module [_](Recent.module-type-S1.argument-1-_.md) + +# Signature \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md new file mode 100644 index 0000000000..86d7107480 --- /dev/null +++ b/test/generators/markdown/Recent_impl.B.md @@ -0,0 +1,13 @@ +Recent_impl + +B + +Module Recent_impl.B + + + +###### type t = + + + +######    | B \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.Foo.A.md b/test/generators/markdown/Recent_impl.Foo.A.md new file mode 100644 index 0000000000..23f1a90837 --- /dev/null +++ b/test/generators/markdown/Recent_impl.Foo.A.md @@ -0,0 +1,15 @@ +Recent_impl + +Foo + +A + +Module Foo.A + + + +###### type t = + + + +######    | A \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.Foo.B.md b/test/generators/markdown/Recent_impl.Foo.B.md new file mode 100644 index 0000000000..3dd136dc0a --- /dev/null +++ b/test/generators/markdown/Recent_impl.Foo.B.md @@ -0,0 +1,15 @@ +Recent_impl + +Foo + +B + +Module Foo.B + + + +###### type t = + + + +######    | B \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.Foo.md b/test/generators/markdown/Recent_impl.Foo.md new file mode 100644 index 0000000000..3d7864dd60 --- /dev/null +++ b/test/generators/markdown/Recent_impl.Foo.md @@ -0,0 +1,13 @@ +Recent_impl + +Foo + +Module Recent_impl.Foo + + + +###### module [A](Recent_impl.Foo.A.md) + + + +###### module [B](Recent_impl.Foo.B.md) \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.md b/test/generators/markdown/Recent_impl.md new file mode 100644 index 0000000000..9587407c22 --- /dev/null +++ b/test/generators/markdown/Recent_impl.md @@ -0,0 +1,25 @@ +Recent_impl + +Module Recent_impl + + + +###### module [Foo](Recent_impl.Foo.md) + + + +###### module [B](Recent_impl.B.md) + + + +###### type u + + + +###### module type [S](Recent_impl.module-type-S.md) + + + +###### module B' = + +> [Foo.B](Recent_impl.Foo.B.md) diff --git a/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md b/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md new file mode 100644 index 0000000000..1bcfc3532b --- /dev/null +++ b/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md @@ -0,0 +1,9 @@ +Recent_impl + +S + +F + +1-_ + +Parameter F.1-_ \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.module-type-S.F.md b/test/generators/markdown/Recent_impl.module-type-S.F.md new file mode 100644 index 0000000000..3a6fcc4fe1 --- /dev/null +++ b/test/generators/markdown/Recent_impl.module-type-S.F.md @@ -0,0 +1,19 @@ +Recent_impl + +S + +F + +Module S.F + +# Parameters + + + +###### module [_](Recent_impl.module-type-S.F.argument-1-_.md) + +# Signature + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.module-type-S.X.md b/test/generators/markdown/Recent_impl.module-type-S.X.md new file mode 100644 index 0000000000..ad1aa0bf60 --- /dev/null +++ b/test/generators/markdown/Recent_impl.module-type-S.X.md @@ -0,0 +1,7 @@ +Recent_impl + +S + +X + +Module S.X \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.module-type-S.md b/test/generators/markdown/Recent_impl.module-type-S.md new file mode 100644 index 0000000000..45a3fc82c0 --- /dev/null +++ b/test/generators/markdown/Recent_impl.module-type-S.md @@ -0,0 +1,19 @@ +Recent_impl + +S + +Module type Recent_impl.S + + + +###### module [F](Recent_impl.module-type-S.F.md) + + + +###### module [X](Recent_impl.module-type-S.X.md) + + + +###### val f : + +> [F(X).t](Recent_impl.module-type-S.F.md#type-t) diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md new file mode 100644 index 0000000000..7d1da64559 --- /dev/null +++ b/test/generators/markdown/Section.md @@ -0,0 +1,36 @@ +Section + +Module Section + +This is the module comment. Eventually, sections won't be allowed in it. + +# Empty section + +# Text only + +Foo bar. + +# Aside only + +Foo bar. + +# Value only + + + +###### val foo : + +> unit + + +# Empty section + +# within a comment + +## and one with a nested section + +--- + +# _This_ section **title** has markup + +But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. \ No newline at end of file diff --git a/test/generators/markdown/Stop.N.md b/test/generators/markdown/Stop.N.md new file mode 100644 index 0000000000..4c3a4846f8 --- /dev/null +++ b/test/generators/markdown/Stop.N.md @@ -0,0 +1,11 @@ +Stop + +N + +Module Stop.N + + + +###### val quux : + +> int diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md new file mode 100644 index 0000000000..5cc6980553 --- /dev/null +++ b/test/generators/markdown/Stop.md @@ -0,0 +1,30 @@ +Stop + +Module Stop + +This test cases exercises stop comments. + + + +###### val foo : + +> int + + +This is normal commented text. + +The next value is bar , and it should be missing from the documentation. There is also an entire module, M , which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. + +Documentation is on again. + +Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module. + + + +###### module [N](Stop.N.md) + + + +###### val lol : + +> int diff --git a/test/generators/markdown/Stop_dead_link_doc.Foo.md b/test/generators/markdown/Stop_dead_link_doc.Foo.md new file mode 100644 index 0000000000..c9f285b2b2 --- /dev/null +++ b/test/generators/markdown/Stop_dead_link_doc.Foo.md @@ -0,0 +1,9 @@ +Stop_dead_link_doc + +Foo + +Module Stop_dead_link_doc.Foo + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md new file mode 100644 index 0000000000..f466ad47a9 --- /dev/null +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -0,0 +1,61 @@ +Stop_dead_link_doc + +Module Stop_dead_link_doc + + + +###### module [Foo](Stop_dead_link_doc.Foo.md) + + + +###### type foo = + + + +######    | Bar of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) + + + +###### type bar = + + + +######    | Bar of { + + + +######    field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t) ; + +} + + + +###### type foo_ = + + + +######    | Bar_ of int * [Foo.t](Stop_dead_link_doc.Foo.md#type-t) * int + + + +###### type bar_ = + + + +######    | Bar__ of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) option + + + +###### type another_foo + + + +###### type another_bar + + + +###### type another_foo_ + + + +###### type another_bar_ \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Alias.md b/test/generators/markdown/Toplevel_comments.Alias.md new file mode 100644 index 0000000000..65bdfdd6c2 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.Alias.md @@ -0,0 +1,13 @@ +Toplevel_comments + +Alias + +Module Toplevel_comments.Alias + +Doc of Alias . + +Doc of T , part 2. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md new file mode 100644 index 0000000000..ca771f9b42 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md @@ -0,0 +1,11 @@ +Toplevel_comments + +Comments_on_open + +M + +Module Comments_on_open.M + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md new file mode 100644 index 0000000000..6c4d450449 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -0,0 +1,15 @@ +Toplevel_comments + +Comments_on_open + +Module Toplevel_comments.Comments_on_open + + + +###### module [M](Toplevel_comments.Comments_on_open.M.md) + +## Section + +--- + +Comments attached to open are treated as floating comments. Referencing [Section](#sec) [M.t](Toplevel_comments.Comments_on_open.M.md#type-t) works \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Include_inline'.md b/test/generators/markdown/Toplevel_comments.Include_inline'.md new file mode 100644 index 0000000000..bf834649e9 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.Include_inline'.md @@ -0,0 +1,13 @@ +Toplevel_comments + +Include_inline' + +Module Toplevel_comments.Include_inline' + +Doc of Include_inline , part 1. + +Doc of Include_inline , part 2. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Include_inline.md b/test/generators/markdown/Toplevel_comments.Include_inline.md new file mode 100644 index 0000000000..8022368f62 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.Include_inline.md @@ -0,0 +1,11 @@ +Toplevel_comments + +Include_inline + +Module Toplevel_comments.Include_inline + +Doc of T , part 2. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.M''.md b/test/generators/markdown/Toplevel_comments.M''.md new file mode 100644 index 0000000000..f9071f503f --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.M''.md @@ -0,0 +1,9 @@ +Toplevel_comments + +M'' + +Module Toplevel_comments.M'' + +Doc of M'' , part 1. + +Doc of M'' , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.M'.md b/test/generators/markdown/Toplevel_comments.M'.md new file mode 100644 index 0000000000..2bb36648a1 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.M'.md @@ -0,0 +1,7 @@ +Toplevel_comments + +M' + +Module Toplevel_comments.M' + +Doc of M' from outside \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.M.md b/test/generators/markdown/Toplevel_comments.M.md new file mode 100644 index 0000000000..c8f121c8cd --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.M.md @@ -0,0 +1,7 @@ +Toplevel_comments + +M + +Module Toplevel_comments.M + +Doc of M \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md new file mode 100644 index 0000000000..9ff17ab301 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -0,0 +1,13 @@ +Toplevel_comments + +Ref_in_synopsis + +Module Toplevel_comments.Ref_in_synopsis + +[t](#type-t) . + +This reference should resolve in the context of this module, even when used as a synopsis. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.c1.md b/test/generators/markdown/Toplevel_comments.c1.md new file mode 100644 index 0000000000..3b1e120bf1 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.c1.md @@ -0,0 +1,9 @@ +Toplevel_comments + +c1 + +Class Toplevel_comments.c1 + +Doc of c1 , part 1. + +Doc of c1 , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.c2.md b/test/generators/markdown/Toplevel_comments.c2.md new file mode 100644 index 0000000000..dccbd59122 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.c2.md @@ -0,0 +1,9 @@ +Toplevel_comments + +c2 + +Class Toplevel_comments.c2 + +Doc of c2 . + +Doc of ct , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.class-type-ct.md b/test/generators/markdown/Toplevel_comments.class-type-ct.md new file mode 100644 index 0000000000..62eaf06f50 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.class-type-ct.md @@ -0,0 +1,9 @@ +Toplevel_comments + +ct + +Class type Toplevel_comments.ct + +Doc of ct , part 1. + +Doc of ct , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md new file mode 100644 index 0000000000..07f5940cf0 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.md @@ -0,0 +1,87 @@ +Toplevel_comments + +Module Toplevel_comments + +A doc comment at the beginning of a module is considered to be that module's doc. + + + +###### module type [T](Toplevel_comments.module-type-T.md) + +Doc of `T` + + + +###### module [Include_inline](Toplevel_comments.Include_inline.md) + +Doc of `T` + + + +###### module [Include_inline'](Toplevel_comments.Include_inline'.md) + +Doc of `Include_inline` + + + +###### module type [Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) + +Doc of `T` + + + +###### module type [Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) + +Doc of `Include_inline_T'` + + + +###### module [M](Toplevel_comments.M.md) + +Doc of `M` + + + +###### module [M'](Toplevel_comments.M'.md) + +Doc of `M'` + + + +###### module [M''](Toplevel_comments.M''.md) + +Doc of `M''` + + + +###### module [Alias](Toplevel_comments.Alias.md) + +Doc of `Alias` + + + +###### class [c1](Toplevel_comments.c1.md) + +Doc of `c1` + + + +###### class type [ct](Toplevel_comments.class-type-ct.md) + +Doc of `ct` + + + +###### class [c2](Toplevel_comments.c2.md) + +Doc of `c2` + + + +###### module [Ref_in_synopsis](Toplevel_comments.Ref_in_synopsis.md) + + + + + +###### module [Comments_on_open](Toplevel_comments.Comments_on_open.md) \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md new file mode 100644 index 0000000000..d9418541c8 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md @@ -0,0 +1,13 @@ +Toplevel_comments + +Include_inline_T' + +Module type Toplevel_comments.Include_inline_T' + +Doc of Include_inline_T' , part 1. + +Doc of Include_inline_T' , part 2. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md new file mode 100644 index 0000000000..588ad6e418 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md @@ -0,0 +1,11 @@ +Toplevel_comments + +Include_inline_T + +Module type Toplevel_comments.Include_inline_T + +Doc of T , part 2. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.module-type-T.md b/test/generators/markdown/Toplevel_comments.module-type-T.md new file mode 100644 index 0000000000..a0590073a6 --- /dev/null +++ b/test/generators/markdown/Toplevel_comments.module-type-T.md @@ -0,0 +1,13 @@ +Toplevel_comments + +T + +Module type Toplevel_comments.T + +Doc of T , part 1. + +Doc of T , part 2. + + + +###### type t \ No newline at end of file diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md new file mode 100644 index 0000000000..fbd15c0778 --- /dev/null +++ b/test/generators/markdown/Type.md @@ -0,0 +1,452 @@ +Type + +Module Type + + + +###### type abstract + +Some + + + +###### type alias = + +> int + + + + +###### type private_ = + +> private int + + + + +###### type 'a constructor = + +> 'a + + + + +###### type arrow = + +> int -> int + + + + +###### type higher_order = + +> ( int -> int ) -> int + + + + +###### type labeled = + +> l : int -> int + + + + +###### type optional = + +> ? l : int -> int + + + + +###### type labeled_higher_order = + +> ( l : int -> int ) -> ( ? l : int -> int ) -> int + + + + +###### type pair = + +> int * int + + + + +###### type parens_dropped = + +> int * int + + + + +###### type triple = + +> int * int * int + + + + +###### type nested_pair = + +> ( int * int ) * int + + + + +###### type instance = + +> int [constructor](#type-constructor) + + + + +###### type long = + +> [labeled_higher_order](#type-labeled_higher_order) -> [ `Bar | `Baz of [triple](#type-triple) ] -> [pair](#type-pair) -> [labeled](#type-labeled) -> [higher_order](#type-higher_order) -> ( string -> int ) -> ( int * float * char * string * char * unit ) option -> [nested_pair](#type-nested_pair) -> [arrow](#type-arrow) -> string -> [nested_pair](#type-nested_pair) array + + + + +###### type variant_e = { + + + +######    a : int ; + +} + + + +###### type variant = + + + +######    | A + + + +######    | B of int + + + +######    | C + +foo + + + +######    | D + + + + + +######    | E of [variant_e](#type-variant_e) + + + +###### type variant_c = { + + + +######    a : int ; + +} + + + +###### type _ gadt = + + + +######    | A : int [gadt](#type-gadt) + + + +######    | B : int -> + + + +######    | C : [variant_c](#type-variant_c) -> + + + +###### type degenerate_gadt = + + + +######    | A : [degenerate_gadt](#type-degenerate_gadt) + + + +###### type private_variant = private + + + +######    | A + + + +###### type record = { + + + +######    a : int ; + + + +######    mutable b : int ; + + + +######    c : int ; + +foo + + + +######    d : int ; + + + + + +######    e : 'a. 'a ; + +} + + + +###### type polymorphic_variant = [ + + + +######    | `A + + + +######    | `B of int + + + +######    | `C of int * unit + + + +######    | `D + +] + + + +###### type polymorphic_variant_extension = [ + + + +######    | [polymorphic_variant](#type-polymorphic_variant) + + + +######    | `E + +] + + + +###### type nested_polymorphic_variant = [ + + + +######    | `A of [ `B | `C ] + +] + + + +###### type private_extenion#row + + + +###### and private_extenion = private [> + + + +######    | [polymorphic_variant](#type-polymorphic_variant) + +] + + + +###### type object_ = + +> < a : int ; b : int ; c : int > + + + + +###### module type [X](Type.module-type-X.md) + + + +###### type module_ = + +> ( module [X](Type.module-type-X.md) ) + + + + +###### type module_substitution = + +> ( module [X](Type.module-type-X.md) with type [t](Type.module-type-X.md#type-t) = int and type [u](Type.module-type-X.md#type-u) = unit ) + + + + +###### type +'a covariant + + + +###### type -'a contravariant + + + +###### type _ bivariant = + +> int + + + + +###### type ('a, 'b) binary + + + +###### type using_binary = + +> ( int , int ) [binary](#type-binary) + + + + +###### type 'custom name + + + +###### type 'a constrained = + +> 'a constraint 'a = int + + + + +###### type 'a exact_variant = + +> 'a constraint 'a = [ `A | `B of int ] + + + + +###### type 'a lower_variant = + +> 'a constraint 'a = [> `A | `B of int ] + + + + +###### type 'a any_variant = + +> 'a constraint 'a = [> ] + + + + +###### type 'a upper_variant = + +> 'a constraint 'a = [< `A | `B of int ] + + + + +###### type 'a named_variant = + +> 'a constraint 'a = [< [polymorphic_variant](#type-polymorphic_variant) ] + + + + +###### type 'a exact_object = + +> 'a constraint 'a = < a : int ; b : int > + + + + +###### type 'a lower_object = + +> 'a constraint 'a = < a : int ; b : int .. > + + + + +###### type 'a poly_object = + +> 'a constraint 'a = < a : 'a. 'a > + + + + +###### type ('a, 'b) double_constrained = + +> 'a * 'b constraint 'a = int constraint 'b = unit + + + + +###### type as_ = + +> int as ' a * 'a + + + + +###### type extensible = + +> .. + + + + +###### type [extensible](#type-extensible) += + + + +######    | Extension + +Documentation for + + + +######    | Another_extension + +Documentation for + + + +###### type mutually = + + + +######    | A of [recursive](#type-recursive) + + + +###### and recursive = + + + +######    | B of [mutually](#type-mutually) + + + +###### exception Foo of int * int \ No newline at end of file diff --git a/test/generators/markdown/Type.module-type-X.md b/test/generators/markdown/Type.module-type-X.md new file mode 100644 index 0000000000..517c602e08 --- /dev/null +++ b/test/generators/markdown/Type.module-type-X.md @@ -0,0 +1,13 @@ +Type + +X + +Module type Type.X + + + +###### type t + + + +###### type u \ No newline at end of file diff --git a/test/generators/markdown/Val.md b/test/generators/markdown/Val.md new file mode 100644 index 0000000000..ea6fc17163 --- /dev/null +++ b/test/generators/markdown/Val.md @@ -0,0 +1,28 @@ +Val + +Module Val + + + +###### val documented : + +> unit + + +Foo. + + + +###### val undocumented : + +> unit + + + + +###### val documented_above : + +> unit + + +Bar. \ No newline at end of file diff --git a/test/generators/markdown/alias.targets b/test/generators/markdown/alias.targets new file mode 100644 index 0000000000..53bf0edee2 --- /dev/null +++ b/test/generators/markdown/alias.targets @@ -0,0 +1,2 @@ +Alias.md +Alias.X.md diff --git a/test/generators/markdown/bugs.targets b/test/generators/markdown/bugs.targets new file mode 100644 index 0000000000..f4ac3a475d --- /dev/null +++ b/test/generators/markdown/bugs.targets @@ -0,0 +1 @@ +Bugs.md diff --git a/test/generators/markdown/bugs_post_406.targets b/test/generators/markdown/bugs_post_406.targets new file mode 100644 index 0000000000..977e656e7e --- /dev/null +++ b/test/generators/markdown/bugs_post_406.targets @@ -0,0 +1,3 @@ +Bugs_post_406.md +Bugs_post_406.class-type-let_open.md +Bugs_post_406.let_open'.md diff --git a/test/generators/markdown/class.targets b/test/generators/markdown/class.targets new file mode 100644 index 0000000000..3ab4b4fd34 --- /dev/null +++ b/test/generators/markdown/class.targets @@ -0,0 +1,10 @@ +Class.md +Class.class-type-empty.md +Class.class-type-mutually.md +Class.class-type-recursive.md +Class.mutually'.md +Class.recursive'.md +Class.class-type-empty_virtual.md +Class.empty_virtual'.md +Class.class-type-polymorphic.md +Class.polymorphic'.md diff --git a/test/generators/markdown/external.targets b/test/generators/markdown/external.targets new file mode 100644 index 0000000000..6151f8c64f --- /dev/null +++ b/test/generators/markdown/external.targets @@ -0,0 +1 @@ +External.md diff --git a/test/generators/markdown/functor.targets b/test/generators/markdown/functor.targets new file mode 100644 index 0000000000..5af55e4e0f --- /dev/null +++ b/test/generators/markdown/functor.targets @@ -0,0 +1,13 @@ +Functor.md +Functor.module-type-S.md +Functor.module-type-S1.md +Functor.module-type-S1.argument-1-_.md +Functor.F1.md +Functor.F1.argument-1-Arg.md +Functor.F2.md +Functor.F2.argument-1-Arg.md +Functor.F3.md +Functor.F3.argument-1-Arg.md +Functor.F4.md +Functor.F4.argument-1-Arg.md +Functor.F5.md diff --git a/test/generators/markdown/functor2.targets b/test/generators/markdown/functor2.targets new file mode 100644 index 0000000000..31a8163860 --- /dev/null +++ b/test/generators/markdown/functor2.targets @@ -0,0 +1,8 @@ +Functor2.md +Functor2.module-type-S.md +Functor2.X.md +Functor2.X.argument-1-Y.md +Functor2.X.argument-2-Z.md +Functor2.module-type-XF.md +Functor2.module-type-XF.argument-1-Y.md +Functor2.module-type-XF.argument-2-Z.md diff --git a/test/generators/markdown/include.targets b/test/generators/markdown/include.targets new file mode 100644 index 0000000000..de945e7c30 --- /dev/null +++ b/test/generators/markdown/include.targets @@ -0,0 +1,7 @@ +Include.md +Include.module-type-Not_inlined.md +Include.module-type-Inlined.md +Include.module-type-Not_inlined_and_closed.md +Include.module-type-Not_inlined_and_opened.md +Include.module-type-Inherent_Module.md +Include.module-type-Dorminant_Module.md diff --git a/test/generators/markdown/include2.targets b/test/generators/markdown/include2.targets new file mode 100644 index 0000000000..b048561857 --- /dev/null +++ b/test/generators/markdown/include2.targets @@ -0,0 +1,5 @@ +Include2.md +Include2.X.md +Include2.Y.md +Include2.Y_include_synopsis.md +Include2.Y_include_doc.md diff --git a/test/generators/markdown/include_sections.targets b/test/generators/markdown/include_sections.targets new file mode 100644 index 0000000000..217fdd37d7 --- /dev/null +++ b/test/generators/markdown/include_sections.targets @@ -0,0 +1,2 @@ +Include_sections.md +Include_sections.module-type-Something.md diff --git a/test/generators/markdown/interlude.targets b/test/generators/markdown/interlude.targets new file mode 100644 index 0000000000..71d1c93d24 --- /dev/null +++ b/test/generators/markdown/interlude.targets @@ -0,0 +1 @@ +Interlude.md diff --git a/test/generators/markdown/labels.targets b/test/generators/markdown/labels.targets new file mode 100644 index 0000000000..2bd92d59e6 --- /dev/null +++ b/test/generators/markdown/labels.targets @@ -0,0 +1,5 @@ +Labels.md +Labels.A.md +Labels.module-type-S.md +Labels.c.md +Labels.class-type-cs.md diff --git a/test/generators/markdown/markup.targets b/test/generators/markdown/markup.targets new file mode 100644 index 0000000000..50ee6d91a1 --- /dev/null +++ b/test/generators/markdown/markup.targets @@ -0,0 +1,3 @@ +Markup.md +Markup.X.md +Markup.Y.md diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md new file mode 100644 index 0000000000..0f9e26567b --- /dev/null +++ b/test/generators/markdown/mld.md @@ -0,0 +1,41 @@ +mld + + Mld Page + +--- + +This is an .mld file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. + +It will have a TOC generated from section headings. + +# Section + +This is a section. + +Another paragraph in section. + +# Another section + +This is another section. + +Another paragraph in section 2. + +## Subsection + +--- + +This is a subsection. + +Another paragraph in subsection. + +Yet another paragraph in subsection. + +## Another Subsection + +--- + +This is another subsection. + +Another paragraph in subsection 2. + +Yet another paragraph in subsection 2. \ No newline at end of file diff --git a/test/generators/markdown/module.targets b/test/generators/markdown/module.targets new file mode 100644 index 0000000000..1b36a542a9 --- /dev/null +++ b/test/generators/markdown/module.targets @@ -0,0 +1,17 @@ +Module.md +Module.module-type-S.md +Module.module-type-S.M.md +Module.module-type-S3.md +Module.module-type-S3.M.md +Module.module-type-S4.md +Module.module-type-S4.M.md +Module.module-type-S5.md +Module.module-type-S5.M.md +Module.module-type-S6.md +Module.module-type-S6.M.md +Module.M'.md +Module.module-type-S7.md +Module.module-type-S8.md +Module.module-type-S9.md +Module.Mutually.md +Module.Recursive.md diff --git a/test/generators/markdown/module_type_alias.targets b/test/generators/markdown/module_type_alias.targets new file mode 100644 index 0000000000..e57a19cc69 --- /dev/null +++ b/test/generators/markdown/module_type_alias.targets @@ -0,0 +1,9 @@ +Module_type_alias.md +Module_type_alias.module-type-A.md +Module_type_alias.module-type-B.md +Module_type_alias.module-type-B.argument-1-C.md +Module_type_alias.module-type-E.md +Module_type_alias.module-type-E.argument-1-F.md +Module_type_alias.module-type-E.argument-2-C.md +Module_type_alias.module-type-G.md +Module_type_alias.module-type-G.argument-1-H.md diff --git a/test/generators/markdown/module_type_subst.targets b/test/generators/markdown/module_type_subst.targets new file mode 100644 index 0000000000..02313c3dbf --- /dev/null +++ b/test/generators/markdown/module_type_subst.targets @@ -0,0 +1,36 @@ +Module_type_subst.md +Module_type_subst.Local.md +Module_type_subst.Local.module-type-local.md +Module_type_subst.Local.module-type-s.md +Module_type_subst.module-type-s.md +Module_type_subst.Basic.md +Module_type_subst.Basic.module-type-u.md +Module_type_subst.Basic.module-type-u.module-type-T.md +Module_type_subst.Basic.module-type-with_.md +Module_type_subst.Basic.module-type-u2.md +Module_type_subst.Basic.module-type-u2.module-type-T.md +Module_type_subst.Basic.module-type-u2.M.md +Module_type_subst.Basic.module-type-with_2.md +Module_type_subst.Basic.module-type-with_2.module-type-T.md +Module_type_subst.Basic.module-type-with_2.M.md +Module_type_subst.Basic.module-type-a.md +Module_type_subst.Basic.module-type-a.M.md +Module_type_subst.Basic.module-type-c.md +Module_type_subst.Basic.module-type-c.M.md +Module_type_subst.Nested.md +Module_type_subst.Nested.module-type-nested.md +Module_type_subst.Nested.module-type-nested.N.md +Module_type_subst.Nested.module-type-nested.N.module-type-t.md +Module_type_subst.Nested.module-type-with_.md +Module_type_subst.Nested.module-type-with_.N.md +Module_type_subst.Nested.module-type-with_subst.md +Module_type_subst.Nested.module-type-with_subst.N.md +Module_type_subst.Structural.md +Module_type_subst.Structural.module-type-u.md +Module_type_subst.Structural.module-type-u.module-type-a.md +Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md +Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md +Module_type_subst.Structural.module-type-w.md +Module_type_subst.Structural.module-type-w.module-type-a.md +Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md +Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md diff --git a/test/generators/markdown/nested.targets b/test/generators/markdown/nested.targets new file mode 100644 index 0000000000..f19e793a4b --- /dev/null +++ b/test/generators/markdown/nested.targets @@ -0,0 +1,8 @@ +Nested.md +Nested.X.md +Nested.module-type-Y.md +Nested.F.md +Nested.F.argument-1-Arg1.md +Nested.F.argument-2-Arg2.md +Nested.z.md +Nested.inherits.md diff --git a/test/generators/markdown/ocamlary.targets b/test/generators/markdown/ocamlary.targets new file mode 100644 index 0000000000..c2a17e70ce --- /dev/null +++ b/test/generators/markdown/ocamlary.targets @@ -0,0 +1,182 @@ +Ocamlary.md +Ocamlary.Empty.md +Ocamlary.module-type-Empty.md +Ocamlary.module-type-MissingComment.md +Ocamlary.module-type-EmptySig.md +Ocamlary.ModuleWithSignature.md +Ocamlary.ModuleWithSignatureAlias.md +Ocamlary.One.md +Ocamlary.module-type-SigForMod.md +Ocamlary.module-type-SigForMod.Inner.md +Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md +Ocamlary.module-type-SuperSig.md +Ocamlary.module-type-SuperSig.module-type-SubSigA.md +Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md +Ocamlary.module-type-SuperSig.module-type-SubSigB.md +Ocamlary.module-type-SuperSig.module-type-EmptySig.md +Ocamlary.module-type-SuperSig.module-type-One.md +Ocamlary.module-type-SuperSig.module-type-SuperSig.md +Ocamlary.Buffer.md +Ocamlary.CollectionModule.md +Ocamlary.CollectionModule.InnerModuleA.md +Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md +Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-COLLECTION.md +Ocamlary.module-type-COLLECTION.InnerModuleA.md +Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md +Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.Recollection.md +Ocamlary.Recollection.argument-1-C.md +Ocamlary.Recollection.argument-1-C.InnerModuleA.md +Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md +Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.Recollection.InnerModuleA.md +Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md +Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-MMM.md +Ocamlary.module-type-MMM.C.md +Ocamlary.module-type-MMM.C.InnerModuleA.md +Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md +Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-RECOLLECTION.md +Ocamlary.module-type-RecollectionModule.md +Ocamlary.module-type-RecollectionModule.InnerModuleA.md +Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md +Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-A.md +Ocamlary.module-type-A.Q.md +Ocamlary.module-type-A.Q.InnerModuleA.md +Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md +Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-B.md +Ocamlary.module-type-B.Q.md +Ocamlary.module-type-B.Q.InnerModuleA.md +Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md +Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-C.md +Ocamlary.module-type-C.Q.md +Ocamlary.module-type-C.Q.InnerModuleA.md +Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md +Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.FunctorTypeOf.md +Ocamlary.FunctorTypeOf.argument-1-Collection.md +Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md +Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md +Ocamlary.module-type-IncludeModuleType.md +Ocamlary.module-type-ToInclude.md +Ocamlary.module-type-ToInclude.IncludedA.md +Ocamlary.module-type-ToInclude.module-type-IncludedB.md +Ocamlary.IncludedA.md +Ocamlary.module-type-IncludedB.md +Ocamlary.ExtMod.md +Ocamlary.empty_class.md +Ocamlary.one_method_class.md +Ocamlary.two_method_class.md +Ocamlary.param_class.md +Ocamlary.Dep1.md +Ocamlary.Dep1.module-type-S.md +Ocamlary.Dep1.module-type-S.c.md +Ocamlary.Dep1.X.md +Ocamlary.Dep1.X.Y.md +Ocamlary.Dep1.X.Y.c.md +Ocamlary.Dep2.md +Ocamlary.Dep2.argument-1-Arg.md +Ocamlary.Dep2.argument-1-Arg.X.md +Ocamlary.Dep2.A.md +Ocamlary.Dep3.md +Ocamlary.Dep4.md +Ocamlary.Dep4.module-type-T.md +Ocamlary.Dep4.module-type-S.md +Ocamlary.Dep4.module-type-S.X.md +Ocamlary.Dep4.module-type-S.Y.md +Ocamlary.Dep4.X.md +Ocamlary.Dep5.md +Ocamlary.Dep5.argument-1-Arg.md +Ocamlary.Dep5.argument-1-Arg.module-type-S.md +Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md +Ocamlary.Dep5.Z.md +Ocamlary.Dep6.md +Ocamlary.Dep6.module-type-S.md +Ocamlary.Dep6.module-type-T.md +Ocamlary.Dep6.module-type-T.Y.md +Ocamlary.Dep6.X.md +Ocamlary.Dep6.X.Y.md +Ocamlary.Dep7.md +Ocamlary.Dep7.argument-1-Arg.md +Ocamlary.Dep7.argument-1-Arg.module-type-T.md +Ocamlary.Dep7.argument-1-Arg.X.md +Ocamlary.Dep7.M.md +Ocamlary.Dep8.md +Ocamlary.Dep8.module-type-T.md +Ocamlary.Dep9.md +Ocamlary.Dep9.argument-1-X.md +Ocamlary.module-type-Dep10.md +Ocamlary.Dep11.md +Ocamlary.Dep11.module-type-S.md +Ocamlary.Dep11.module-type-S.c.md +Ocamlary.Dep12.md +Ocamlary.Dep12.argument-1-Arg.md +Ocamlary.Dep13.md +Ocamlary.Dep13.c.md +Ocamlary.module-type-With1.md +Ocamlary.module-type-With1.M.md +Ocamlary.With2.md +Ocamlary.With2.module-type-S.md +Ocamlary.With3.md +Ocamlary.With3.N.md +Ocamlary.With4.md +Ocamlary.With4.N.md +Ocamlary.With5.md +Ocamlary.With5.module-type-S.md +Ocamlary.With5.N.md +Ocamlary.With6.md +Ocamlary.With6.module-type-T.md +Ocamlary.With6.module-type-T.M.md +Ocamlary.With7.md +Ocamlary.With7.argument-1-X.md +Ocamlary.module-type-With8.md +Ocamlary.module-type-With8.M.md +Ocamlary.module-type-With8.M.N.md +Ocamlary.With9.md +Ocamlary.With9.module-type-S.md +Ocamlary.With10.md +Ocamlary.With10.module-type-T.md +Ocamlary.With10.module-type-T.M.md +Ocamlary.module-type-With11.md +Ocamlary.module-type-With11.N.md +Ocamlary.module-type-NestedInclude1.md +Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md +Ocamlary.module-type-NestedInclude2.md +Ocamlary.DoubleInclude1.md +Ocamlary.DoubleInclude1.DoubleInclude2.md +Ocamlary.DoubleInclude3.md +Ocamlary.DoubleInclude3.DoubleInclude2.md +Ocamlary.IncludeInclude1.md +Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md +Ocamlary.IncludeInclude1.IncludeInclude2_M.md +Ocamlary.module-type-IncludeInclude2.md +Ocamlary.IncludeInclude2_M.md +Ocamlary.CanonicalTest.md +Ocamlary.CanonicalTest.Base.md +Ocamlary.CanonicalTest.Base.List.md +Ocamlary.CanonicalTest.Base_Tests.md +Ocamlary.CanonicalTest.Base_Tests.C.md +Ocamlary.CanonicalTest.List_modif.md +Ocamlary.Aliases.md +Ocamlary.Aliases.Foo.md +Ocamlary.Aliases.Foo.A.md +Ocamlary.Aliases.Foo.B.md +Ocamlary.Aliases.Foo.C.md +Ocamlary.Aliases.Foo.D.md +Ocamlary.Aliases.Foo.E.md +Ocamlary.Aliases.Std.md +Ocamlary.Aliases.E.md +Ocamlary.Aliases.P1.md +Ocamlary.Aliases.P1.Y.md +Ocamlary.Aliases.P2.md +Ocamlary.module-type-M.md +Ocamlary.M.md +Ocamlary.Only_a_module.md +Ocamlary.module-type-TypeExt.md +Ocamlary.module-type-TypeExtPruned.md diff --git a/test/generators/markdown/page-mld.targets b/test/generators/markdown/page-mld.targets new file mode 100644 index 0000000000..24638fb1c8 --- /dev/null +++ b/test/generators/markdown/page-mld.targets @@ -0,0 +1 @@ +mld.md diff --git a/test/generators/markdown/recent.targets b/test/generators/markdown/recent.targets new file mode 100644 index 0000000000..db6aaf9c26 --- /dev/null +++ b/test/generators/markdown/recent.targets @@ -0,0 +1,9 @@ +Recent.md +Recent.module-type-S.md +Recent.module-type-S1.md +Recent.module-type-S1.argument-1-_.md +Recent.Z.md +Recent.Z.Y.md +Recent.Z.Y.X.md +Recent.X.md +Recent.module-type-PolyS.md diff --git a/test/generators/markdown/recent_impl.targets b/test/generators/markdown/recent_impl.targets new file mode 100644 index 0000000000..fba358f0b8 --- /dev/null +++ b/test/generators/markdown/recent_impl.targets @@ -0,0 +1,9 @@ +Recent_impl.md +Recent_impl.Foo.md +Recent_impl.Foo.A.md +Recent_impl.Foo.B.md +Recent_impl.B.md +Recent_impl.module-type-S.md +Recent_impl.module-type-S.F.md +Recent_impl.module-type-S.F.argument-1-_.md +Recent_impl.module-type-S.X.md diff --git a/test/generators/markdown/section.targets b/test/generators/markdown/section.targets new file mode 100644 index 0000000000..fd90179afb --- /dev/null +++ b/test/generators/markdown/section.targets @@ -0,0 +1 @@ +Section.md diff --git a/test/generators/markdown/stop.targets b/test/generators/markdown/stop.targets new file mode 100644 index 0000000000..8e7281daf7 --- /dev/null +++ b/test/generators/markdown/stop.targets @@ -0,0 +1,2 @@ +Stop.md +Stop.N.md diff --git a/test/generators/markdown/stop_dead_link_doc.targets b/test/generators/markdown/stop_dead_link_doc.targets new file mode 100644 index 0000000000..c49fe54c7a --- /dev/null +++ b/test/generators/markdown/stop_dead_link_doc.targets @@ -0,0 +1,2 @@ +Stop_dead_link_doc.md +Stop_dead_link_doc.Foo.md diff --git a/test/generators/markdown/toplevel_comments.targets b/test/generators/markdown/toplevel_comments.targets new file mode 100644 index 0000000000..065eae2c44 --- /dev/null +++ b/test/generators/markdown/toplevel_comments.targets @@ -0,0 +1,16 @@ +Toplevel_comments.md +Toplevel_comments.module-type-T.md +Toplevel_comments.Include_inline.md +Toplevel_comments.Include_inline'.md +Toplevel_comments.module-type-Include_inline_T.md +Toplevel_comments.module-type-Include_inline_T'.md +Toplevel_comments.M.md +Toplevel_comments.M'.md +Toplevel_comments.M''.md +Toplevel_comments.Alias.md +Toplevel_comments.c1.md +Toplevel_comments.class-type-ct.md +Toplevel_comments.c2.md +Toplevel_comments.Ref_in_synopsis.md +Toplevel_comments.Comments_on_open.md +Toplevel_comments.Comments_on_open.M.md diff --git a/test/generators/markdown/type.targets b/test/generators/markdown/type.targets new file mode 100644 index 0000000000..2520f313c6 --- /dev/null +++ b/test/generators/markdown/type.targets @@ -0,0 +1,2 @@ +Type.md +Type.module-type-X.md diff --git a/test/generators/markdown/val.targets b/test/generators/markdown/val.targets new file mode 100644 index 0000000000..48c8111582 --- /dev/null +++ b/test/generators/markdown/val.targets @@ -0,0 +1 @@ +Val.md diff --git a/test/integration/markdown.t/intf.mli b/test/integration/markdown.t/intf.mli deleted file mode 100644 index a55bbd5846..0000000000 --- a/test/integration/markdown.t/intf.mli +++ /dev/null @@ -1,47 +0,0 @@ -(** Synopsis. - - Rest of preamble. *) - -(** Floating comment at the top. *) - -type t -(** Doc for [type t]. *) - -val x : t -(** Doc for [val x]. *) - -type a = t -(** Type alias *) - -(** Doc for [type b]. *) -type b = A (** Doc for [A]. *) | B (** Doc for [B]. *) - -type c = { a : int; (** Doc for [a]. *) b : int (** Doc for [b]. *) } -(** Doc for [type c]. *) - -val y : [ `One (** Doc for [`One]. *) | `Two (** Doc for [`Two]. *) ] -(** Polymorphic variant. *) - -(** Floating comment. *) - -val z : t -> (t -> t) -> foo:t -> ?bar:t -> [ `One of t ] -> t * t -(** Type complicated enough to be rendered differently. *) - -(** Outer doc for [M]. *) -module M : sig - (** Inner doc for [M]. *) - - type t -end - -module N : sig - (** Doc for [N]. *) - - type t -end - -module type S = sig - (** Doc for [S]. *) - - type t -end diff --git a/test/integration/markdown.t/markup.mli b/test/integration/markdown.t/markup.mli deleted file mode 100644 index 5644997de4..0000000000 --- a/test/integration/markdown.t/markup.mli +++ /dev/null @@ -1,72 +0,0 @@ -(** {1 This is a heading }*) - -(** {2:label This has a label}*) - -(** arrow (->) in a doc comment *) - -(** {%html:foo:bar%} : a raw markup *) - -(** {2:foo Label} *) - -(** {{:href} test_two } *) - -(** {{:href} {b test}} *) - -(** {{:href} test two foo } *) - -(** {{:href} **barz** } *) - -(** {v -verbatim -text -v} *) - -(** See if listness is preserved. *) - -(** This is an {i interface} with {b all} of the {e module system} features. - This documentation demonstrates: -- comment formatting -- unassociated comments -- documentation sections -- module system documentation including - {ol - {- submodules} - {- module aliases} - {- module types} - {- module type aliases} - {- modules with signatures} - {- modules with aliased signatures} -} - -A numbered list: -+ 3 -+ 2 -+ 1 - - David Sheets is the author. - @author David Sheets -*) - -(** p1 *) - -(** p2 - - p3 - - {ul - {- a} - {- b} - } *) - -(** This is where I begin my thing from. *) - -(** {ol - {- one} - {- two} - } *) - -(** {ul - {- Mon} - {- Tue} - } *) - diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t deleted file mode 100644 index 3be0c2191e..0000000000 --- a/test/integration/markdown.t/run.t +++ /dev/null @@ -1,214 +0,0 @@ - $ ocamlc -c -bin-annot intf.mli markup.mli - $ odoc compile intf.cmti - $ odoc compile markup.cmti - $ odoc link intf.odoc - $ odoc link markup.odoc - $ odoc markdown-generate intf.odocl -o markdown --generate-links - $ odoc markdown-generate markup.odocl -o markdown --generate-links - - $ find markdown - markdown - markdown/Intf.md - markdown/Markup.md - markdown/Intf.N.md - markdown/Intf.module-type-S.md - markdown/Intf.M.md - - $ cat markdown/Intf.md - Intf - - Module Intf - - Synopsis. - - Rest of preamble. - - Floating comment at the top. - - - - ###### type t - - Doc for `type t` - - - - ###### val x : - - > [t](#type-t) - - - Doc for `val x` - - - - ###### type a = - - > [t](#type-t) - - - Type alias - - - - ###### type b = - - - - ######    | A - - Doc for `A` - - - - ######    | B - - Doc for `B` - - Doc for `type b` - - - - ###### type c = { - - - - ######    a : int ; - - Doc for `a` - - - - ######    b : int ; - - Doc for `b` - - } - - Doc for `type c` - - - - ###### val y : - - > [ `One | `Two ] - - - Polymorphic variant. - - Floating comment. - - - - ###### val z : - - > [t](#type-t) -> ( [t](#type-t) -> [t](#type-t) ) -> foo : [t](#type-t) -> ? bar : [t](#type-t) -> [ `One of [t](#type-t) ] -> [t](#type-t) * [t](#type-t) - - - Type complicated enough to be rendered differently. - - - - ###### module [M](Intf.M.md) - - Outer doc for `M` - - - - ###### module [N](Intf.N.md) - - Doc for `N` - - - - ###### module type [S](Intf.module-type-S.md) - - Doc for `S` - - $ cat markdown/Markup.md - Markup - - Module Markup - - # This is a heading - - ## This has a label - - --- - - arrow (->) in a doc comment - - foo:bar : a raw markup - - ## Label - - --- - - [test_two](href) - - [**test**](href) - - [test two foo](href) - - [**barz**](href) - - ``` - verbatim - text - ``` - - See if listness is preserved. - - This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: - - - comment formatting - - - unassociated comments - - - documentation sections - - - module system documentation including - - 1. submodules - - 2. module aliases - - 3. module types - - 4. module type aliases - - 5. modules with signatures - - 6. modules with aliased signatures - - A numbered list: - - 1. 3 - - 2. 2 - - 3. 1 - - David Sheets is the author. - - @author: David Sheets - - p1 - - p2 - - p3 - - - a - - - b - - This is where I begin my thing from. - - 1. one - - 2. two - - - Mon - - - Tue From 0da2e62a93991cb4ad21e45e3e990bf8670ac37c Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Wed, 2 Feb 2022 16:46:08 +0100 Subject: [PATCH 17/38] Cleanup blocks concatenation --- src/markdown/generator.ml | 44 ++++++++++++++++---------------- src/markdown/link.ml | 3 +-- src/markdown/markup.ml | 9 ++++--- src/markdown/markup.mli | 53 ++++++++++++++++++++++----------------- 4 files changed, 57 insertions(+), 52 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 63e2b34c8b..19d1c1eff7 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -99,18 +99,14 @@ and inline (l : Inline.t) args = | Source content -> source_code content args ++ continue rest | Raw_markup (_, s) -> text s ++ continue rest) -let rec blocks' (bs : blocks list) = - match bs with - | [] -> paragraph noop - | [ b ] -> b - | b :: rest -> blocks b (blocks' rest) +let fold_blocks f elts : blocks = + List.fold_left (fun acc elt -> acc +++ f elt) noop_block elts let rec block (l : Block.t) args = - let noop = paragraph noop in match l with - | [] -> noop + | [] -> noop_block | b :: rest -> ( - let continue r = if r = [] then noop else block r args in + let continue r = if r = [] then noop_block else block r args in match b.desc with | Inline i -> blocks (paragraph (inline i args)) (continue rest) | Paragraph i -> blocks (paragraph (inline i args)) (continue rest) @@ -137,7 +133,7 @@ let rec block (l : Block.t) args = in paragraph (join (text "@") (join key (text ":")) ++ def) in - blocks (blocks' (List.map f descrs)) (continue rest) + blocks (fold_blocks f descrs) (continue rest) | Source content -> blocks (paragraph (source_code content args)) (continue rest) | Verbatim content -> blocks (code_block content) (continue rest) @@ -204,7 +200,8 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = paragraph (source_code c args) +++ continue rest else continue rest | Alternative (Expansion { url; expansion; _ }) -> - if Link.should_inline url then documented_src expansion args nesting_level + if Link.should_inline url then + documented_src expansion args nesting_level else continue rest | Subpage p -> blocks (subpage p.content args (nesting_level + 1)) (continue rest) @@ -220,7 +217,7 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = let f (content, doc, (anchor : Odoc_document.Url.t option)) = let doc = match doc with - | [] -> noop + | [] -> noop_block | doc -> paragraph (text (acc_text doc)) in let content = @@ -242,7 +239,7 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = blocks (paragraph (anchor' anchor)) item else item in - blocks (blocks' (List.map f lines)) (continue rest)) + blocks (fold_blocks f lines) (continue rest)) and subpage { title = _; header = _; items; url = _ } args nesting_level = let content = items in @@ -250,11 +247,12 @@ and subpage { title = _; header = _; items; url = _ } args nesting_level = subpage' @@ item content args nesting_level and item (l : Item.t list) args nesting_level = - let noop = paragraph noop in match l with - | [] -> noop + | [] -> noop_block | i :: rest -> ( - let continue r = if r = [] then noop else item r args nesting_level in + let continue r = + if r = [] then noop_block else item r args nesting_level + in match i with | Text b -> blocks (block b args) (continue rest) | Heading { Heading.label; level; title } -> @@ -294,7 +292,7 @@ and item (l : Item.t list) args nesting_level = let render_declaration ~anchor ~doc heading content = let doc = match doc with - | [] -> noop + | [] -> noop_block | doc -> paragraph (text (acc_text doc)) and anchor = if args.generate_links then @@ -302,7 +300,7 @@ and item (l : Item.t list) args nesting_level = match anchor with Some x -> x.Url.Anchor.anchor | None -> "" in paragraph (anchor' anchor) - else noop + else noop_block in anchor +++ item_heading nesting_level (source_code heading args) @@ -315,7 +313,7 @@ and item (l : Item.t list) args nesting_level = let content = if source_contains_text content then quote_block (paragraph (source_code content args)) - else noop + else noop_block in render_declaration ~anchor ~doc code content | code, content -> @@ -334,17 +332,17 @@ and item (l : Item.t list) args nesting_level = let page ~generate_links { Page.header; items; url; _ } = let args = { base_path = url; generate_links } in - let blocks'' l = List.map (fun s -> paragraph (text s)) l |> blocks' in - blocks' - ([ blocks'' (Link.for_printing url) ] - @ [ blocks (item header args 0) (item items args 0) ]) + fold_blocks (fun s -> paragraph (text s)) (Link.for_printing url) + +++ item header args 0 +++ item items args 0 let rec subpage ~generate_links subp = let p = subp.Subpage.content in if Link.should_inline p.url then [] else [ render ~generate_links p ] and render ~generate_links (p : Page.t) = - let content fmt = Format.fprintf fmt "%a" pp_blocks (page ~generate_links p) in + let content fmt = + Format.fprintf fmt "%a" pp_blocks (page ~generate_links p) + in let children = Utils.flatmap ~f:(fun sp -> subpage ~generate_links sp) (Subpages.compute p) in diff --git a/src/markdown/link.ml b/src/markdown/link.ml index be7592b814..99c7238cd0 100644 --- a/src/markdown/link.ml +++ b/src/markdown/link.ml @@ -34,5 +34,4 @@ let href ~base_path (url : Url.t) = let should_inline _ = false -let files_of_url url = - if should_inline url then [] else [ as_filename url ] +let files_of_url url = if should_inline url then [] else [ as_filename url ] diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 5b66883750..b50b29f07e 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -13,7 +13,7 @@ type inlines = | Linebreak | Noop -and blocks = +type blocks = | ConcatB of blocks * blocks | Block of inlines | CodeBlock of string @@ -67,6 +67,8 @@ let code_block s = CodeBlock s let quote_block b = Prefixed_block ("> ", b) +let noop_block = Block Noop + let heading level i = let make_hashes n = String.make n '#' in let hashes = make_hashes level in @@ -100,10 +102,9 @@ let rec pp_inlines fmt i = let rec pp_blocks fmt b = match b with + | ConcatB (Block Noop, b) | ConcatB (b, Block Noop) -> pp_blocks fmt b | ConcatB (above, below) -> - if above = paragraph noop then pp_blocks fmt below - else if below = paragraph noop then pp_blocks fmt above - else Format.fprintf fmt "%a@\n@\n%a" pp_blocks above pp_blocks below + Format.fprintf fmt "%a@\n@\n%a" pp_blocks above pp_blocks below | Block i -> pp_inlines fmt i | CodeBlock s -> Format.fprintf fmt "```@\n%s@\n```" s | Block_separator -> Format.fprintf fmt "---" diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index ce78a8f807..7d6d00d00e 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -1,38 +1,24 @@ -(** The goal of this module is to allow to describe a markdown document and - to print it. - A markdown document is composed of [blocks]. *) +(** The goal of this module is to allow to describe a markdown document and to + print it. A markdown document is composed of {!blocks}, see {!pp_blocks}. *) + +(** {2 Inline elements} *) type inlines -(** Inlines elements are rendered one after the other, separated by spaces, - but not by empty line. *) +(** Inlines elements are rendered one after the other, separated by spaces. *) val ( ++ ) : inlines -> inlines -> inlines -(** Combine inlines. *) +(** Combine inlines, render a breakable space between two inlines. *) val join : inlines -> inlines -> inlines - -type blocks -(** A block is composed of [inlines]. Blocks are separated by an empty line. *) - -val ordered_list : blocks list -> blocks - -val unordered_list : blocks list -> blocks - -val ( +++ ) : blocks -> blocks -> blocks -(** Alias for {!blocks} *) - -val blocks : blocks -> blocks -> blocks -(** Combine blocks. *) - -val block_separator : blocks -(** A horizontal line between a heading and the body. *) +(** Join inlines without spaces in between. *) val text : string -> inlines -(** Some inline elements *) +(** An arbitrary string. *) val line_break : inlines val noop : inlines +(** Nothing. Isn't separated by spaces: [noop ++ x = x ++ noop = x]. *) val bold : inlines -> inlines @@ -47,6 +33,24 @@ val link : href:string -> inlines -> inlines val anchor' : string -> inlines +(** {2 Block elements} *) + +type blocks +(** Blocks are separated by an empty line. *) + +val ordered_list : blocks list -> blocks + +val unordered_list : blocks list -> blocks + +val ( +++ ) : blocks -> blocks -> blocks +(** Alias for {!blocks} *) + +val blocks : blocks -> blocks -> blocks +(** Combine blocks. *) + +val block_separator : blocks +(** A horizontal line. *) + val raw_markup : string -> blocks val code_span : string -> string @@ -59,5 +63,8 @@ val quote_block : blocks -> blocks val heading : int -> inlines -> blocks +val noop_block : blocks +(** No blocks. [noop_block +++ x = x +++ noop_block = x]. *) + val pp_blocks : Format.formatter -> blocks -> unit (** Renders a markdown document. *) From 1fc35ece125feb9a389904bf925d8240d738529f Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 19:40:18 +0100 Subject: [PATCH 18/38] Cleanup iteration code --- src/markdown/generator.ml | 116 ++++++++---------- test/generators/markdown/Markup.md | 22 ++-- .../Ocamlary.ModuleWithSignatureAlias.md | 2 +- test/generators/markdown/Ocamlary.md | 8 +- 4 files changed, 65 insertions(+), 83 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 19d1c1eff7..c47bb45f67 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -19,6 +19,9 @@ let style (style : style) = | `Superscript -> superscript | `Subscript -> subscript +let fold_blocks f elts : blocks = + List.fold_left (fun acc elt -> acc +++ f elt) noop_block elts + type args = { base_path : Url.Path.t; generate_links : bool } let rec source_contains_text (s : Source.t) = @@ -59,85 +62,69 @@ let source_take_until_punctuation code = let rec source_code (s : Source.t) args = match s with | [] -> noop - | h :: t -> ( - let continue s = - if source_contains_text s then source_code s args else noop - in - match h with - | Source.Elt i -> inline i args ++ continue t - | Tag (Some "arrow", _) -> - text "->" (* takes care of the Entity branch of Inline.t *) - | Tag (_, s) -> continue s ++ continue t) + | _ when not (source_contains_text s) -> noop + | Source.Elt i :: t -> inline i args ++ source_code t args + | Tag (Some "arrow", _) :: _ -> + text "->" (* takes care of the Entity branch of Inline.t *) + | Tag (_, s) :: t -> source_code s args ++ source_code t args and inline (l : Inline.t) args = match l with | [] -> noop | i :: rest -> ( - let continue i = if i = [] then noop else inline i args in match i.desc with - | Text "" | Text " " -> continue rest + | Text "" | Text " " -> inline rest args | Text _ -> let l, _, rest = Doctree.Take.until l ~classify:(function | { Inline.desc = Text s; _ } -> Accum [ s ] | _ -> Stop_and_keep) in - text String.(concat "" l |> trim) ++ continue rest + text String.(concat "" l |> trim) ++ inline rest args | Entity _ -> noop - | Styled (styl, content) -> style styl (continue content) ++ continue rest - | Linebreak -> line_break ++ continue rest + | Styled (styl, content) -> + style styl (inline content args) ++ inline rest args + | Linebreak -> line_break ++ inline rest args | Link (href, content) -> - link ~href (inline content args) ++ continue rest + link ~href (inline content args) ++ inline rest args | InternalLink (Resolved (url, content)) -> if args.generate_links then link ~href:(Link.href ~base_path:args.base_path url) (inline content args) - ++ continue rest - else continue content ++ continue rest - | InternalLink (Unresolved content) -> continue content ++ continue rest - | Source content -> source_code content args ++ continue rest - | Raw_markup (_, s) -> text s ++ continue rest) + ++ inline rest args + else inline content args ++ inline rest args + | InternalLink (Unresolved content) -> + inline content args ++ inline rest args + | Source content -> source_code content args ++ inline rest args + | Raw_markup (_, s) -> text s ++ inline rest args) -let fold_blocks f elts : blocks = - List.fold_left (fun acc elt -> acc +++ f elt) noop_block elts +let rec block args l = fold_blocks (block_one args) l -let rec block (l : Block.t) args = - match l with - | [] -> noop_block - | b :: rest -> ( - let continue r = if r = [] then noop_block else block r args in - match b.desc with - | Inline i -> blocks (paragraph (inline i args)) (continue rest) - | Paragraph i -> blocks (paragraph (inline i args)) (continue rest) - | List (list_typ, l') -> - let f bs = - match list_typ with - | Unordered -> unordered_list bs - | Ordered -> ordered_list bs - in - blocks (f (List.map (fun b -> block b args) l')) (continue rest) - | Description _ -> - let descrs, _, rest = - Take.until l ~classify:(function - | { Block.desc = Description l; _ } -> Accum l - | _ -> Stop_and_keep) - in - let f i = - let key = inline i.Description.key args in - let def = - match i.Description.definition with - | [] -> text "" - | h :: _ -> ( - match h.desc with Inline i -> inline i args | _ -> text "") - in - paragraph (join (text "@") (join key (text ":")) ++ def) - in - blocks (fold_blocks f descrs) (continue rest) - | Source content -> - blocks (paragraph (source_code content args)) (continue rest) - | Verbatim content -> blocks (code_block content) (continue rest) - | Raw_markup (_, s) -> blocks (raw_markup s) (continue rest)) +and block_one args b = + match b.Block.desc with + | Inline i -> paragraph (inline i args) + | Paragraph i -> paragraph (inline i args) + | List (list_typ, items) -> ( + let items = List.map (block args) items in + match list_typ with + | Unordered -> unordered_list items + | Ordered -> ordered_list items) + | Description l -> description args l + | Source content -> paragraph (source_code content args) + | Verbatim content -> code_block content + | Raw_markup (_, s) -> raw_markup s + +and description args l = fold_blocks (description_one args) l + +and description_one args { Description.key; definition; _ } = + let key = inline key args in + let def = + match definition with + | [] -> noop + | h :: _ -> ( match h.desc with Inline i -> inline i args | _ -> noop) + in + paragraph (join (text "@") (join key (text ":")) ++ def) let rec acc_text (l : Block.t) : string = match l with @@ -186,13 +173,10 @@ let take_code l = (c, rest) let rec documented_src (l : DocumentedSrc.t) args nesting_level = - let noop = paragraph noop in match l with - | [] -> noop + | [] -> noop_block | line :: rest -> ( - let continue r = - if r = [] then noop else documented_src r args nesting_level - in + let continue r = documented_src r args nesting_level in match line with | Code s -> if source_contains_text s then @@ -250,11 +234,9 @@ and item (l : Item.t list) args nesting_level = match l with | [] -> noop_block | i :: rest -> ( - let continue r = - if r = [] then noop_block else item r args nesting_level - in + let continue r = item r args nesting_level in match i with - | Text b -> blocks (block b args) (continue rest) + | Text b -> blocks (block args b) (continue rest) | Heading { Heading.label; level; title } -> let heading' = let title = inline title args in diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 50fd8bd180..8f331d9db7 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -131,11 +131,11 @@ Raw HTML can be as inline elements in # Modules -@[X](Markup.X.md): +@[X](Markup.X.md): -@[X](Markup.X.md): +@[X](Markup.X.md): -@[Y](Markup.Y.md): +@[Y](Markup.Y.md): # Tags @@ -143,23 +143,23 @@ Each comment can end with zero or more tags. Here are some examples: @author: antron -@deprecated: +@deprecated: -@parameter foo: +@parameter foo: -@raises Failure: +@raises Failure: -@returns: +@returns: -@see [#](#): +@see [#](#): -@see foo.ml: +@see foo.ml: -@see Foo: +@see Foo: @since: 0 -@before 1.0: +@before 1.0: @version: -1 diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md index e4194270d4..64ba31e2b6 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md @@ -6,4 +6,4 @@ Module Ocamlary.ModuleWithSignatureAlias A plain module with an alias signature -@deprecated: \ No newline at end of file +@deprecated: \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index c275f3737b..5d6bc1db69 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -1256,9 +1256,9 @@ With ocamldoc, toplevel units will be linked and documented, while submodules wi With odoc, everything should be resolved (and linked) but only toplevel units will be documented. -@[Dep1.X](Ocamlary.Dep1.X.md): +@[Dep1.X](Ocamlary.Dep1.X.md): -@[Ocamlary.IncludeInclude1](Ocamlary.IncludeInclude1.md): +@[Ocamlary.IncludeInclude1](Ocamlary.IncludeInclude1.md): @[Ocamlary](): This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: @@ -1266,9 +1266,9 @@ With odoc, everything should be resolved (and linked) but only toplevel units wi --- -@[IncludeInclude1.IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md): +@[IncludeInclude1.IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md): -@[Dep4.X](Ocamlary.Dep4.X.md): +@[Dep4.X](Ocamlary.Dep4.X.md): # Playing with @canonical paths From 654d4a0e1ec31efbbac13aae812cbfe7be8ad9dd Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 20:02:23 +0100 Subject: [PATCH 19/38] Make sure noops are removed from concatenations Noops shouldn't be present in the tree to respect the contract: noop ++ x = x ++ noop = x Remove the special handling of Text nodes that was a work around this. --- src/markdown/generator.ml | 52 +++++++++++++++++---------------------- src/markdown/markup.ml | 5 +++- 2 files changed, 26 insertions(+), 31 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index c47bb45f67..112f5ed9fa 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -19,6 +19,9 @@ let style (style : style) = | `Superscript -> superscript | `Subscript -> subscript +let fold_inlines f elts : inlines = + List.fold_left (fun acc elt -> acc ++ f elt) noop elts + let fold_blocks f elts : blocks = List.fold_left (fun acc elt -> acc +++ f elt) noop_block elts @@ -68,36 +71,25 @@ let rec source_code (s : Source.t) args = text "->" (* takes care of the Entity branch of Inline.t *) | Tag (_, s) :: t -> source_code s args ++ source_code t args -and inline (l : Inline.t) args = - match l with - | [] -> noop - | i :: rest -> ( - match i.desc with - | Text "" | Text " " -> inline rest args - | Text _ -> - let l, _, rest = - Doctree.Take.until l ~classify:(function - | { Inline.desc = Text s; _ } -> Accum [ s ] - | _ -> Stop_and_keep) - in - text String.(concat "" l |> trim) ++ inline rest args - | Entity _ -> noop - | Styled (styl, content) -> - style styl (inline content args) ++ inline rest args - | Linebreak -> line_break ++ inline rest args - | Link (href, content) -> - link ~href (inline content args) ++ inline rest args - | InternalLink (Resolved (url, content)) -> - if args.generate_links then - link - ~href:(Link.href ~base_path:args.base_path url) - (inline content args) - ++ inline rest args - else inline content args ++ inline rest args - | InternalLink (Unresolved content) -> - inline content args ++ inline rest args - | Source content -> source_code content args ++ inline rest args - | Raw_markup (_, s) -> text s ++ inline rest args) +and inline l args = fold_inlines (inline_one args) l + +and inline_one args i = + match i.Inline.desc with + | Text ("" | " ") -> noop + | Text s -> text (String.trim s) + | Entity _ -> noop + | Styled (styl, content) -> style styl (inline content args) + | Linebreak -> line_break + | Link (href, content) -> link ~href (inline content args) + | InternalLink (Resolved (url, content)) -> + if args.generate_links then + link + ~href:(Link.href ~base_path:args.base_path url) + (inline content args) + else inline content args + | InternalLink (Unresolved content) -> inline content args + | Source content -> source_code content args + | Raw_markup (_, s) -> text s let rec block args l = fold_blocks (block_one args) l diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index b50b29f07e..934fdd3b2c 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -28,7 +28,10 @@ let ordered_list bs = List (Ordered, bs) let unordered_list bs = List (Unordered, bs) -let ( ++ ) left right = ConcatI (left, right) +(* Make sure to never leave a [Noop] in the result, which would cause unwanted + spaces. *) +let ( ++ ) left right = + match (left, right) with Noop, x | x, Noop -> x | _ -> ConcatI (left, right) let join left right = Join (left, right) From 69a08bec8ad94e699dc2c5e0be383e0b41826ab0 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 20:04:41 +0100 Subject: [PATCH 20/38] Document: Remove empty text nodes This is not a requirement but helps when inspecting the document. --- src/document/codefmt.ml | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/document/codefmt.ml b/src/document/codefmt.ml index a66f3496d7..0c60b7b1a1 100644 --- a/src/document/codefmt.ml +++ b/src/document/codefmt.ml @@ -28,11 +28,12 @@ module State = struct ()) let leave state = - if state.ignore_all = 0 then ( + if state.ignore_all = 0 then let current_elt = List.rev state.current in let previous_elt, tag = Stack.pop state.context in - state.current <- Tag (tag, current_elt) :: previous_elt; - ()) + match current_elt with + | [] -> state.current <- previous_elt + | _ -> state.current <- Tag (tag, current_elt) :: previous_elt let rec flush state = if Stack.is_empty state.context then List.rev state.current @@ -151,7 +152,9 @@ let make () = let open Inline in let state0 = State.create () in let push elt = State.push state0 (Elt elt) in - let push_text s = if state0.ignore_all = 0 then push [ inline @@ Text s ] in + let push_text s = + if state0.ignore_all = 0 && s <> "" then push [ inline @@ Text s ] + in let formatter = let out_string s i j = push_text (String.sub s i j) in From 9bbc31af64173c46bfb195320e853bb19aae0c28 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 20:08:52 +0100 Subject: [PATCH 21/38] Fix bits of source code incorrectly removed --- src/markdown/generator.ml | 14 ++++++-------- test/generators/markdown/Ocamlary.md | 18 +++++++++--------- test/generators/markdown/Recent.md | 8 ++++---- test/generators/markdown/Type.md | 4 ++-- 4 files changed, 21 insertions(+), 23 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 112f5ed9fa..21e96de661 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -62,14 +62,12 @@ let source_take_until_punctuation code = if is_punctuation i then Stop_and_accum ([ t ], None) else Accum [ t ] | Tag (_, c) -> Rec c) -let rec source_code (s : Source.t) args = - match s with - | [] -> noop - | _ when not (source_contains_text s) -> noop - | Source.Elt i :: t -> inline i args ++ source_code t args - | Tag (Some "arrow", _) :: _ -> - text "->" (* takes care of the Entity branch of Inline.t *) - | Tag (_, s) :: t -> source_code s args ++ source_code t args +let rec source_code (s : Source.t) args = fold_inlines (source_code_one args) s + +and source_code_one args = function + | Source.Elt i -> inline i args + | Tag (Some "arrow", _) -> text "->" + | Tag (_, s) -> source_code s args and inline l args = fold_inlines (inline_one args) l diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 5d6bc1db69..9e716a0e19 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -584,15 +584,15 @@ This comment is for `poly_variant`Wow! It was a polymorphic variant! -######    | First : 'a -> +######    | First : 'a -> ( 'a , unit ) [full_gadt](#type-full_gadt) -######    | Second : 'a -> +######    | Second : 'a -> ( unit , 'a ) [full_gadt](#type-full_gadt) -######    | Exist : 'a * 'b -> +######    | Exist : 'a * 'b -> ( 'b , unit ) [full_gadt](#type-full_gadt) This comment is for `full_gadt`Wow! It was a GADT! @@ -610,7 +610,7 @@ This comment is for `full_gadt`Wow! It was a GADT! -######    | ExistGadtTag : ( 'a -> 'b ) -> +######    | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt](#type-partial_gadt) This comment is for `partial_gadt`Wow! It was a mixed GADT! @@ -791,15 +791,15 @@ This comment is for `poly_variant_union` -######    | First : 'a -> +######    | First : 'a -> ( 'a , unit ) [full_gadt_alias](#type-full_gadt_alias) -######    | Second : 'a -> +######    | Second : 'a -> ( unit , 'a ) [full_gadt_alias](#type-full_gadt_alias) -######    | Exist : 'a * 'b -> +######    | Exist : 'a * 'b -> ( 'b , unit ) [full_gadt_alias](#type-full_gadt_alias) This comment is for `full_gadt_alias` @@ -817,7 +817,7 @@ This comment is for `full_gadt_alias` -######    | ExistGadtTag : ( 'a -> 'b ) -> +######    | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt_alias](#type-partial_gadt_alias) This comment is for `partial_gadt_alias` @@ -825,7 +825,7 @@ This comment is for `partial_gadt_alias` ###### exception Exn_arrow : -> unit -> +> unit -> exn This comment is for diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 389ea13229..ab98cd4790 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -54,7 +54,7 @@ foo -######    | B : int -> +######    | B : int -> string [gadt](#type-gadt) foo @@ -66,7 +66,7 @@ foo ######    a : int ; -} -> +} -> unit [gadt](#type-gadt) @@ -114,7 +114,7 @@ bar -######    | X : [< `X of & 'a & int * float ] -> +######    | X : [< `X of & 'a & int * float ] -> [empty_conj](#type-empty_conj) @@ -122,7 +122,7 @@ bar -######    | X : [< `X of int & [< `B of int & float ] ] -> +######    | X : [< `X of int & [< `B of int & float ] ] -> [conj](#type-conj) diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index fbd15c0778..2be8a7a05d 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -164,11 +164,11 @@ foo -######    | B : int -> +######    | B : int -> string [gadt](#type-gadt) -######    | C : [variant_c](#type-variant_c) -> +######    | C : [variant_c](#type-variant_c) -> unit [gadt](#type-gadt) From b559088b43f052923ffe61bfc573ad81bdb7dff7 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 20:21:05 +0100 Subject: [PATCH 22/38] Fix printing of code blocks --- src/markdown/generator.ml | 4 ++-- src/markdown/markup.ml | 6 +++--- src/markdown/markup.mli | 2 +- test/generators/markdown/Markup.md | 2 ++ 4 files changed, 8 insertions(+), 6 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 21e96de661..f9205cfbb0 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -101,8 +101,8 @@ and block_one args b = | Unordered -> unordered_list items | Ordered -> ordered_list items) | Description l -> description args l - | Source content -> paragraph (source_code content args) - | Verbatim content -> code_block content + | Source content -> code_block (source_code content args) + | Verbatim content -> code_block (text content) | Raw_markup (_, s) -> raw_markup s and description args l = fold_blocks (description_one args) l diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 934fdd3b2c..b23fbe840a 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -16,7 +16,7 @@ type inlines = type blocks = | ConcatB of blocks * blocks | Block of inlines - | CodeBlock of string + | CodeBlock of inlines | List of list_type * blocks list | Raw_markup of string | Block_separator @@ -66,7 +66,7 @@ let raw_markup s = Raw_markup s let paragraph i = Block i -let code_block s = CodeBlock s +let code_block i = CodeBlock i let quote_block b = Prefixed_block ("> ", b) @@ -109,7 +109,7 @@ let rec pp_blocks fmt b = | ConcatB (above, below) -> Format.fprintf fmt "%a@\n@\n%a" pp_blocks above pp_blocks below | Block i -> pp_inlines fmt i - | CodeBlock s -> Format.fprintf fmt "```@\n%s@\n```" s + | CodeBlock i -> Format.fprintf fmt "```@\n%a@\n```" pp_inlines i | Block_separator -> Format.fprintf fmt "---" | List (list_type, l) -> let rec pp_list n l = diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index 7d6d00d00e..c96f28a35d 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -57,7 +57,7 @@ val code_span : string -> string val paragraph : inlines -> blocks -val code_block : string -> blocks +val code_block : inlines -> blocks val quote_block : blocks -> blocks diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 8f331d9db7..3cbf16e470 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -64,6 +64,7 @@ This is a reference to [foo](#val-foo) . References can have replacement text: [ This is a code block: +``` let foo = () (** There are some nested comments in here, but an unpaired comment terminator would terminate the whole doc surrounding comment. It's @@ -71,6 +72,7 @@ let foo = () let bar = ignore foo +``` There are also verbatim blocks: From a8a859d6414884474b1ce919aea6031c3b50a926 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 20:58:59 +0100 Subject: [PATCH 23/38] Fix printing of code spans --- src/markdown/generator.ml | 28 ++++++ src/markdown/markup.ml | 6 +- src/markdown/markup.mli | 2 +- test/generators/markdown/Alias.X.md | 2 +- test/generators/markdown/Alias.md | 2 +- test/generators/markdown/Bugs.md | 2 +- .../Bugs_post_406.class-type-let_open.md | 2 +- .../markdown/Bugs_post_406.let_open'.md | 2 +- test/generators/markdown/Bugs_post_406.md | 2 +- .../markdown/Class.class-type-empty.md | 2 +- .../Class.class-type-empty_virtual.md | 2 +- .../markdown/Class.class-type-mutually.md | 2 +- .../markdown/Class.class-type-polymorphic.md | 2 +- .../markdown/Class.class-type-recursive.md | 2 +- .../markdown/Class.empty_virtual'.md | 2 +- test/generators/markdown/Class.md | 2 +- test/generators/markdown/Class.mutually'.md | 2 +- .../generators/markdown/Class.polymorphic'.md | 2 +- test/generators/markdown/Class.recursive'.md | 2 +- test/generators/markdown/External.md | 2 +- .../markdown/Functor.F1.argument-1-Arg.md | 2 +- test/generators/markdown/Functor.F1.md | 2 +- .../markdown/Functor.F2.argument-1-Arg.md | 2 +- test/generators/markdown/Functor.F2.md | 2 +- .../markdown/Functor.F3.argument-1-Arg.md | 2 +- test/generators/markdown/Functor.F3.md | 2 +- .../markdown/Functor.F4.argument-1-Arg.md | 2 +- test/generators/markdown/Functor.F4.md | 2 +- test/generators/markdown/Functor.F5.md | 2 +- test/generators/markdown/Functor.md | 2 +- .../markdown/Functor.module-type-S.md | 2 +- .../Functor.module-type-S1.argument-1-_.md | 2 +- .../markdown/Functor.module-type-S1.md | 2 +- .../markdown/Functor2.X.argument-1-Y.md | 2 +- .../markdown/Functor2.X.argument-2-Z.md | 2 +- test/generators/markdown/Functor2.X.md | 2 +- test/generators/markdown/Functor2.md | 2 +- .../markdown/Functor2.module-type-S.md | 2 +- .../Functor2.module-type-XF.argument-1-Y.md | 2 +- .../Functor2.module-type-XF.argument-2-Z.md | 2 +- .../markdown/Functor2.module-type-XF.md | 2 +- test/generators/markdown/Include.md | 2 +- .../Include.module-type-Dorminant_Module.md | 2 +- .../Include.module-type-Inherent_Module.md | 2 +- .../markdown/Include.module-type-Inlined.md | 2 +- .../Include.module-type-Not_inlined.md | 2 +- ...lude.module-type-Not_inlined_and_closed.md | 2 +- ...lude.module-type-Not_inlined_and_opened.md | 2 +- test/generators/markdown/Include2.X.md | 2 +- test/generators/markdown/Include2.Y.md | 2 +- .../markdown/Include2.Y_include_doc.md | 2 +- .../markdown/Include2.Y_include_synopsis.md | 4 +- test/generators/markdown/Include2.md | 2 +- test/generators/markdown/Include_sections.md | 6 +- .../Include_sections.module-type-Something.md | 2 +- test/generators/markdown/Interlude.md | 2 +- test/generators/markdown/Labels.A.md | 2 +- test/generators/markdown/Labels.c.md | 2 +- .../markdown/Labels.class-type-cs.md | 2 +- test/generators/markdown/Labels.md | 2 +- .../markdown/Labels.module-type-S.md | 2 +- test/generators/markdown/Markup.X.md | 2 +- test/generators/markdown/Markup.Y.md | 2 +- test/generators/markdown/Markup.md | 22 ++--- test/generators/markdown/Module.M'.md | 2 +- test/generators/markdown/Module.Mutually.md | 2 +- test/generators/markdown/Module.Recursive.md | 2 +- test/generators/markdown/Module.md | 2 +- .../markdown/Module.module-type-S.M.md | 2 +- .../markdown/Module.module-type-S.md | 2 +- .../markdown/Module.module-type-S3.M.md | 2 +- .../markdown/Module.module-type-S3.md | 2 +- .../markdown/Module.module-type-S4.M.md | 2 +- .../markdown/Module.module-type-S4.md | 2 +- .../markdown/Module.module-type-S5.M.md | 2 +- .../markdown/Module.module-type-S5.md | 2 +- .../markdown/Module.module-type-S6.M.md | 2 +- .../markdown/Module.module-type-S6.md | 2 +- .../markdown/Module.module-type-S7.md | 2 +- .../markdown/Module.module-type-S8.md | 2 +- .../markdown/Module.module-type-S9.md | 2 +- test/generators/markdown/Module_type_alias.md | 2 +- .../Module_type_alias.module-type-A.md | 2 +- ...e_type_alias.module-type-B.argument-1-C.md | 2 +- .../Module_type_alias.module-type-B.md | 2 +- ...e_type_alias.module-type-E.argument-1-F.md | 2 +- ...e_type_alias.module-type-E.argument-2-C.md | 2 +- .../Module_type_alias.module-type-E.md | 2 +- ...e_type_alias.module-type-G.argument-1-H.md | 2 +- .../Module_type_alias.module-type-G.md | 2 +- .../markdown/Module_type_subst.Basic.md | 2 +- ...Module_type_subst.Basic.module-type-a.M.md | 2 +- .../Module_type_subst.Basic.module-type-a.md | 2 +- ...Module_type_subst.Basic.module-type-c.M.md | 2 +- .../Module_type_subst.Basic.module-type-c.md | 2 +- .../Module_type_subst.Basic.module-type-u.md | 2 +- ...subst.Basic.module-type-u.module-type-T.md | 2 +- ...odule_type_subst.Basic.module-type-u2.M.md | 2 +- .../Module_type_subst.Basic.module-type-u2.md | 2 +- ...ubst.Basic.module-type-u2.module-type-T.md | 2 +- ...dule_type_subst.Basic.module-type-with_.md | 2 +- ...e_type_subst.Basic.module-type-with_2.M.md | 2 +- ...ule_type_subst.Basic.module-type-with_2.md | 2 +- ....Basic.module-type-with_2.module-type-T.md | 2 +- .../markdown/Module_type_subst.Local.md | 2 +- ...dule_type_subst.Local.module-type-local.md | 2 +- .../Module_type_subst.Local.module-type-s.md | 2 +- .../markdown/Module_type_subst.Nested.md | 2 +- ..._type_subst.Nested.module-type-nested.N.md | 2 +- ...sted.module-type-nested.N.module-type-t.md | 2 +- ...le_type_subst.Nested.module-type-nested.md | 2 +- ...e_type_subst.Nested.module-type-with_.N.md | 2 +- ...ule_type_subst.Nested.module-type-with_.md | 2 +- ...e_subst.Nested.module-type-with_subst.N.md | 2 +- ...ype_subst.Nested.module-type-with_subst.md | 2 +- .../markdown/Module_type_subst.Structural.md | 2 +- ...ule_type_subst.Structural.module-type-u.md | 2 +- ....Structural.module-type-u.module-type-a.md | 2 +- ...dule-type-u.module-type-a.module-type-b.md | 2 +- ...dule-type-a.module-type-b.module-type-c.md | 2 +- ...ule_type_subst.Structural.module-type-w.md | 2 +- ....Structural.module-type-w.module-type-a.md | 2 +- ...dule-type-w.module-type-a.module-type-b.md | 2 +- ...dule-type-a.module-type-b.module-type-c.md | 2 +- test/generators/markdown/Module_type_subst.md | 2 +- .../Module_type_subst.module-type-s.md | 2 +- .../markdown/Nested.F.argument-1-Arg1.md | 2 +- .../markdown/Nested.F.argument-2-Arg2.md | 2 +- test/generators/markdown/Nested.F.md | 2 +- test/generators/markdown/Nested.X.md | 2 +- test/generators/markdown/Nested.inherits.md | 2 +- test/generators/markdown/Nested.md | 2 +- .../markdown/Nested.module-type-Y.md | 2 +- test/generators/markdown/Nested.z.md | 2 +- .../generators/markdown/Ocamlary.Aliases.E.md | 2 +- .../markdown/Ocamlary.Aliases.Foo.A.md | 2 +- .../markdown/Ocamlary.Aliases.Foo.B.md | 2 +- .../markdown/Ocamlary.Aliases.Foo.C.md | 2 +- .../markdown/Ocamlary.Aliases.Foo.D.md | 2 +- .../markdown/Ocamlary.Aliases.Foo.E.md | 2 +- .../markdown/Ocamlary.Aliases.Foo.md | 2 +- .../markdown/Ocamlary.Aliases.P1.Y.md | 2 +- .../markdown/Ocamlary.Aliases.P1.md | 2 +- .../markdown/Ocamlary.Aliases.P2.md | 2 +- .../markdown/Ocamlary.Aliases.Std.md | 2 +- test/generators/markdown/Ocamlary.Aliases.md | 6 +- test/generators/markdown/Ocamlary.Buffer.md | 4 +- .../Ocamlary.CanonicalTest.Base.List.md | 2 +- .../markdown/Ocamlary.CanonicalTest.Base.md | 2 +- .../Ocamlary.CanonicalTest.Base_Tests.C.md | 2 +- .../Ocamlary.CanonicalTest.Base_Tests.md | 2 +- .../Ocamlary.CanonicalTest.List_modif.md | 2 +- .../markdown/Ocamlary.CanonicalTest.md | 2 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 4 +- .../Ocamlary.CollectionModule.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.CollectionModule.md | 4 +- .../markdown/Ocamlary.Dep1.X.Y.c.md | 2 +- test/generators/markdown/Ocamlary.Dep1.X.Y.md | 2 +- test/generators/markdown/Ocamlary.Dep1.X.md | 2 +- test/generators/markdown/Ocamlary.Dep1.md | 2 +- .../markdown/Ocamlary.Dep1.module-type-S.c.md | 2 +- .../markdown/Ocamlary.Dep1.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.Dep11.md | 2 +- .../Ocamlary.Dep11.module-type-S.c.md | 2 +- .../markdown/Ocamlary.Dep11.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep12.argument-1-Arg.md | 2 +- test/generators/markdown/Ocamlary.Dep12.md | 2 +- test/generators/markdown/Ocamlary.Dep13.c.md | 2 +- test/generators/markdown/Ocamlary.Dep13.md | 2 +- test/generators/markdown/Ocamlary.Dep2.A.md | 2 +- .../Ocamlary.Dep2.argument-1-Arg.X.md | 2 +- .../markdown/Ocamlary.Dep2.argument-1-Arg.md | 2 +- test/generators/markdown/Ocamlary.Dep2.md | 2 +- test/generators/markdown/Ocamlary.Dep3.md | 2 +- test/generators/markdown/Ocamlary.Dep4.X.md | 2 +- test/generators/markdown/Ocamlary.Dep4.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-S.X.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-S.Y.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-T.md | 2 +- test/generators/markdown/Ocamlary.Dep5.Z.md | 2 +- .../markdown/Ocamlary.Dep5.argument-1-Arg.md | 2 +- ...ary.Dep5.argument-1-Arg.module-type-S.Y.md | 2 +- ...mlary.Dep5.argument-1-Arg.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.Dep5.md | 2 +- test/generators/markdown/Ocamlary.Dep6.X.Y.md | 2 +- test/generators/markdown/Ocamlary.Dep6.X.md | 2 +- test/generators/markdown/Ocamlary.Dep6.md | 2 +- .../markdown/Ocamlary.Dep6.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep6.module-type-T.Y.md | 2 +- .../markdown/Ocamlary.Dep6.module-type-T.md | 2 +- test/generators/markdown/Ocamlary.Dep7.M.md | 2 +- .../Ocamlary.Dep7.argument-1-Arg.X.md | 2 +- .../markdown/Ocamlary.Dep7.argument-1-Arg.md | 2 +- ...mlary.Dep7.argument-1-Arg.module-type-T.md | 2 +- test/generators/markdown/Ocamlary.Dep7.md | 2 +- test/generators/markdown/Ocamlary.Dep8.md | 2 +- .../markdown/Ocamlary.Dep8.module-type-T.md | 2 +- .../markdown/Ocamlary.Dep9.argument-1-X.md | 2 +- test/generators/markdown/Ocamlary.Dep9.md | 2 +- .../Ocamlary.DoubleInclude1.DoubleInclude2.md | 2 +- .../markdown/Ocamlary.DoubleInclude1.md | 2 +- .../Ocamlary.DoubleInclude3.DoubleInclude2.md | 2 +- .../markdown/Ocamlary.DoubleInclude3.md | 2 +- test/generators/markdown/Ocamlary.Empty.md | 2 +- test/generators/markdown/Ocamlary.ExtMod.md | 2 +- ...1-Collection.InnerModuleA.InnerModuleA'.md | 4 +- ...peOf.argument-1-Collection.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- ...ary.FunctorTypeOf.argument-1-Collection.md | 4 +- .../markdown/Ocamlary.FunctorTypeOf.md | 4 +- ...mlary.IncludeInclude1.IncludeInclude2_M.md | 2 +- .../markdown/Ocamlary.IncludeInclude1.md | 2 +- ...udeInclude1.module-type-IncludeInclude2.md | 2 +- .../markdown/Ocamlary.IncludeInclude2_M.md | 2 +- .../generators/markdown/Ocamlary.IncludedA.md | 2 +- test/generators/markdown/Ocamlary.M.md | 2 +- .../markdown/Ocamlary.ModuleWithSignature.md | 4 +- .../Ocamlary.ModuleWithSignatureAlias.md | 2 +- test/generators/markdown/Ocamlary.One.md | 2 +- .../markdown/Ocamlary.Only_a_module.md | 2 +- ...Recollection.InnerModuleA.InnerModuleA'.md | 4 +- .../Ocamlary.Recollection.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- ...argument-1-C.InnerModuleA.InnerModuleA'.md | 4 +- ....Recollection.argument-1-C.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../Ocamlary.Recollection.argument-1-C.md | 4 +- .../markdown/Ocamlary.Recollection.md | 4 +- test/generators/markdown/Ocamlary.With10.md | 2 +- .../Ocamlary.With10.module-type-T.M.md | 2 +- .../markdown/Ocamlary.With10.module-type-T.md | 4 +- test/generators/markdown/Ocamlary.With2.md | 2 +- .../markdown/Ocamlary.With2.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.With3.N.md | 2 +- test/generators/markdown/Ocamlary.With3.md | 2 +- test/generators/markdown/Ocamlary.With4.N.md | 2 +- test/generators/markdown/Ocamlary.With4.md | 2 +- test/generators/markdown/Ocamlary.With5.N.md | 2 +- test/generators/markdown/Ocamlary.With5.md | 2 +- .../markdown/Ocamlary.With5.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.With6.md | 2 +- .../Ocamlary.With6.module-type-T.M.md | 2 +- .../markdown/Ocamlary.With6.module-type-T.md | 2 +- .../markdown/Ocamlary.With7.argument-1-X.md | 2 +- test/generators/markdown/Ocamlary.With7.md | 2 +- test/generators/markdown/Ocamlary.With9.md | 2 +- .../markdown/Ocamlary.With9.module-type-S.md | 2 +- .../markdown/Ocamlary.empty_class.md | 2 +- test/generators/markdown/Ocamlary.md | 90 +++++++++---------- ...ule-type-A.Q.InnerModuleA.InnerModuleA'.md | 4 +- .../Ocamlary.module-type-A.Q.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-A.Q.md | 4 +- .../markdown/Ocamlary.module-type-A.md | 2 +- ...ule-type-B.Q.InnerModuleA.InnerModuleA'.md | 4 +- .../Ocamlary.module-type-B.Q.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-B.Q.md | 4 +- .../markdown/Ocamlary.module-type-B.md | 2 +- ...ule-type-C.Q.InnerModuleA.InnerModuleA'.md | 4 +- .../Ocamlary.module-type-C.Q.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-C.Q.md | 4 +- .../markdown/Ocamlary.module-type-C.md | 6 +- ...e-COLLECTION.InnerModuleA.InnerModuleA'.md | 4 +- ...ary.module-type-COLLECTION.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../Ocamlary.module-type-COLLECTION.md | 4 +- .../markdown/Ocamlary.module-type-Dep10.md | 2 +- .../markdown/Ocamlary.module-type-Empty.md | 2 +- .../markdown/Ocamlary.module-type-EmptySig.md | 2 +- .../Ocamlary.module-type-IncludeInclude2.md | 2 +- .../Ocamlary.module-type-IncludeModuleType.md | 4 +- .../Ocamlary.module-type-IncludedB.md | 2 +- .../markdown/Ocamlary.module-type-M.md | 2 +- ...e-type-MMM.C.InnerModuleA.InnerModuleA'.md | 4 +- ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-MMM.C.md | 4 +- .../markdown/Ocamlary.module-type-MMM.md | 2 +- .../Ocamlary.module-type-MissingComment.md | 2 +- .../Ocamlary.module-type-NestedInclude1.md | 2 +- ...stedInclude1.module-type-NestedInclude2.md | 2 +- .../Ocamlary.module-type-NestedInclude2.md | 2 +- .../Ocamlary.module-type-RECOLLECTION.md | 2 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 4 +- ...le-type-RecollectionModule.InnerModuleA.md | 4 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- ...Ocamlary.module-type-RecollectionModule.md | 2 +- .../Ocamlary.module-type-SigForMod.Inner.md | 2 +- ...-type-SigForMod.Inner.module-type-Empty.md | 2 +- .../Ocamlary.module-type-SigForMod.md | 2 +- .../markdown/Ocamlary.module-type-SuperSig.md | 2 +- ...dule-type-SuperSig.module-type-EmptySig.md | 2 +- ...ry.module-type-SuperSig.module-type-One.md | 2 +- ...SuperSig.module-type-SubSigA.SubSigAMod.md | 2 +- ...odule-type-SuperSig.module-type-SubSigA.md | 2 +- ...odule-type-SuperSig.module-type-SubSigB.md | 2 +- ...dule-type-SuperSig.module-type-SuperSig.md | 2 +- ...camlary.module-type-ToInclude.IncludedA.md | 2 +- .../Ocamlary.module-type-ToInclude.md | 2 +- ...le-type-ToInclude.module-type-IncludedB.md | 2 +- .../markdown/Ocamlary.module-type-TypeExt.md | 2 +- .../Ocamlary.module-type-TypeExtPruned.md | 2 +- .../markdown/Ocamlary.module-type-With1.M.md | 2 +- .../markdown/Ocamlary.module-type-With1.md | 2 +- .../markdown/Ocamlary.module-type-With11.N.md | 2 +- .../markdown/Ocamlary.module-type-With11.md | 2 +- .../Ocamlary.module-type-With8.M.N.md | 2 +- .../markdown/Ocamlary.module-type-With8.M.md | 2 +- .../markdown/Ocamlary.module-type-With8.md | 2 +- .../markdown/Ocamlary.one_method_class.md | 2 +- .../markdown/Ocamlary.param_class.md | 2 +- .../markdown/Ocamlary.two_method_class.md | 2 +- test/generators/markdown/Recent.X.md | 2 +- test/generators/markdown/Recent.Z.Y.X.md | 2 +- test/generators/markdown/Recent.Z.Y.md | 2 +- test/generators/markdown/Recent.Z.md | 2 +- test/generators/markdown/Recent.md | 14 +-- .../markdown/Recent.module-type-PolyS.md | 6 +- .../markdown/Recent.module-type-S.md | 2 +- .../Recent.module-type-S1.argument-1-_.md | 2 +- .../markdown/Recent.module-type-S1.md | 2 +- test/generators/markdown/Recent_impl.B.md | 2 +- test/generators/markdown/Recent_impl.Foo.A.md | 2 +- test/generators/markdown/Recent_impl.Foo.B.md | 2 +- test/generators/markdown/Recent_impl.Foo.md | 2 +- test/generators/markdown/Recent_impl.md | 2 +- ...ecent_impl.module-type-S.F.argument-1-_.md | 2 +- .../markdown/Recent_impl.module-type-S.F.md | 2 +- .../markdown/Recent_impl.module-type-S.X.md | 2 +- .../markdown/Recent_impl.module-type-S.md | 2 +- test/generators/markdown/Section.md | 4 +- test/generators/markdown/Stop.N.md | 2 +- test/generators/markdown/Stop.md | 4 +- .../markdown/Stop_dead_link_doc.Foo.md | 2 +- .../generators/markdown/Stop_dead_link_doc.md | 2 +- .../markdown/Toplevel_comments.Alias.md | 6 +- .../Toplevel_comments.Comments_on_open.M.md | 2 +- .../Toplevel_comments.Comments_on_open.md | 4 +- .../Toplevel_comments.Include_inline'.md | 6 +- .../Toplevel_comments.Include_inline.md | 4 +- .../markdown/Toplevel_comments.M''.md | 6 +- .../markdown/Toplevel_comments.M'.md | 4 +- .../markdown/Toplevel_comments.M.md | 4 +- .../Toplevel_comments.Ref_in_synopsis.md | 4 +- .../markdown/Toplevel_comments.c1.md | 6 +- .../markdown/Toplevel_comments.c2.md | 6 +- .../Toplevel_comments.class-type-ct.md | 6 +- test/generators/markdown/Toplevel_comments.md | 2 +- ..._comments.module-type-Include_inline_T'.md | 6 +- ...l_comments.module-type-Include_inline_T.md | 4 +- .../Toplevel_comments.module-type-T.md | 6 +- test/generators/markdown/Type.md | 32 +++---- .../generators/markdown/Type.module-type-X.md | 2 +- test/generators/markdown/Val.md | 2 +- test/generators/markdown/mld.md | 2 +- 359 files changed, 542 insertions(+), 510 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index f9205cfbb0..8162bc31ab 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -41,6 +41,14 @@ let rec source_contains_text (s : Source.t) = in List.exists check_source s +let rec source_contains_only_text s = + let check_inline i = match i.Inline.desc with Text _ -> true | _ -> false in + let check_source = function + | Source.Elt i -> List.for_all check_inline i + | Tag (_, s) -> source_contains_only_text s + in + List.for_all check_source s + (** Split source code at the first [:] or [=]. *) let source_take_until_punctuation code = let rec is_punctuation s i = @@ -62,6 +70,21 @@ let source_take_until_punctuation code = if is_punctuation i then Stop_and_accum ([ t ], None) else Accum [ t ] | Tag (_, c) -> Rec c) +(** Used for code spans. Must be called only on sources that pass + [source_contains_only_text s]. *) +let source_code_to_string s = + let inline acc i = + match i.Inline.desc with Text s -> s :: acc | _ -> assert false + in + let rec source_code s = + List.fold_left + (fun acc -> function + | Source.Elt i -> List.fold_left inline acc i + | Tag (_, t) -> List.rev_append (source_code t) acc) + [] s + in + String.concat "" (List.rev (source_code s)) + let rec source_code (s : Source.t) args = fold_inlines (source_code_one args) s and source_code_one args = function @@ -86,6 +109,8 @@ and inline_one args i = (inline content args) else inline content args | InternalLink (Unresolved content) -> inline content args + | Source content when source_contains_only_text content -> + code_span (source_code_to_string content) | Source content -> source_code content args | Raw_markup (_, s) -> text s @@ -123,6 +148,9 @@ let rec acc_text (l : Block.t) : string = match h.desc with Paragraph i -> inline_text i ^ acc_text rest | _ -> "") and inline_text (i : Inline.t) = + let code_span s = + if String.contains s '`' then "`` " ^ s ^ "``" else "`" ^ s ^ "`" + in match i with | [] -> "" | h :: rest -> ( diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index b23fbe840a..0ff1c7619f 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -56,7 +56,11 @@ let subscript i = Join (String "", Join (i, String "")) let superscript i = Join (String "", Join (i, String "")) let code_span s = - if String.contains s '`' then "`` " ^ s ^ "``" else "`" ^ s ^ "`" + let left, right = + if String.contains s '`' then (String "`` ", String " ``") + else (String "`", String "`") + in + Join (left, Join (String s, right)) let link ~href i = Link (href, i) diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index c96f28a35d..0cfba0cd85 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -53,7 +53,7 @@ val block_separator : blocks val raw_markup : string -> blocks -val code_span : string -> string +val code_span : string -> inlines val paragraph : inlines -> blocks diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md index b650d69e61..26543a75cd 100644 --- a/test/generators/markdown/Alias.X.md +++ b/test/generators/markdown/Alias.X.md @@ -2,7 +2,7 @@ Alias X -Module Alias.X +Module `Alias.X` diff --git a/test/generators/markdown/Alias.md b/test/generators/markdown/Alias.md index eb4448c9cb..8e7b7084d5 100644 --- a/test/generators/markdown/Alias.md +++ b/test/generators/markdown/Alias.md @@ -1,6 +1,6 @@ Alias -Module Alias +Module `Alias` diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index 7a794902b5..748d121f26 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -1,6 +1,6 @@ Bugs -Module Bugs +Module `Bugs` diff --git a/test/generators/markdown/Bugs_post_406.class-type-let_open.md b/test/generators/markdown/Bugs_post_406.class-type-let_open.md index 6b68604881..aec72c2e79 100644 --- a/test/generators/markdown/Bugs_post_406.class-type-let_open.md +++ b/test/generators/markdown/Bugs_post_406.class-type-let_open.md @@ -2,4 +2,4 @@ Bugs_post_406 let_open -Class type Bugs_post_406.let_open \ No newline at end of file +Class type `Bugs_post_406.let_open` \ No newline at end of file diff --git a/test/generators/markdown/Bugs_post_406.let_open'.md b/test/generators/markdown/Bugs_post_406.let_open'.md index 62c319d14c..c879c31fad 100644 --- a/test/generators/markdown/Bugs_post_406.let_open'.md +++ b/test/generators/markdown/Bugs_post_406.let_open'.md @@ -2,4 +2,4 @@ Bugs_post_406 let_open' -Class Bugs_post_406.let_open' \ No newline at end of file +Class `Bugs_post_406.let_open'` \ No newline at end of file diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index 9ab4d4c0e6..eb7f31ff75 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -1,6 +1,6 @@ Bugs_post_406 -Module Bugs_post_406 +Module `Bugs_post_406` Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 diff --git a/test/generators/markdown/Class.class-type-empty.md b/test/generators/markdown/Class.class-type-empty.md index 06e54aec60..18f58446e9 100644 --- a/test/generators/markdown/Class.class-type-empty.md +++ b/test/generators/markdown/Class.class-type-empty.md @@ -2,4 +2,4 @@ Class empty -Class type Class.empty \ No newline at end of file +Class type `Class.empty` \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-empty_virtual.md b/test/generators/markdown/Class.class-type-empty_virtual.md index 546a1971da..1ef5cdce0b 100644 --- a/test/generators/markdown/Class.class-type-empty_virtual.md +++ b/test/generators/markdown/Class.class-type-empty_virtual.md @@ -2,4 +2,4 @@ Class empty_virtual -Class type Class.empty_virtual \ No newline at end of file +Class type `Class.empty_virtual` \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-mutually.md b/test/generators/markdown/Class.class-type-mutually.md index 6b210587b8..ea5ff43f3e 100644 --- a/test/generators/markdown/Class.class-type-mutually.md +++ b/test/generators/markdown/Class.class-type-mutually.md @@ -2,4 +2,4 @@ Class mutually -Class type Class.mutually \ No newline at end of file +Class type `Class.mutually` \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-polymorphic.md b/test/generators/markdown/Class.class-type-polymorphic.md index 5848792d07..c17a11a9a0 100644 --- a/test/generators/markdown/Class.class-type-polymorphic.md +++ b/test/generators/markdown/Class.class-type-polymorphic.md @@ -2,4 +2,4 @@ Class polymorphic -Class type Class.polymorphic \ No newline at end of file +Class type `Class.polymorphic` \ No newline at end of file diff --git a/test/generators/markdown/Class.class-type-recursive.md b/test/generators/markdown/Class.class-type-recursive.md index ddb5752369..bb7b6d3bad 100644 --- a/test/generators/markdown/Class.class-type-recursive.md +++ b/test/generators/markdown/Class.class-type-recursive.md @@ -2,4 +2,4 @@ Class recursive -Class type Class.recursive \ No newline at end of file +Class type `Class.recursive` \ No newline at end of file diff --git a/test/generators/markdown/Class.empty_virtual'.md b/test/generators/markdown/Class.empty_virtual'.md index 9c3d15bced..d9ec1f08e3 100644 --- a/test/generators/markdown/Class.empty_virtual'.md +++ b/test/generators/markdown/Class.empty_virtual'.md @@ -2,4 +2,4 @@ Class empty_virtual' -Class Class.empty_virtual' \ No newline at end of file +Class `Class.empty_virtual'` \ No newline at end of file diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md index bcabfbd22c..fad6889d8c 100644 --- a/test/generators/markdown/Class.md +++ b/test/generators/markdown/Class.md @@ -1,6 +1,6 @@ Class -Module Class +Module `Class` diff --git a/test/generators/markdown/Class.mutually'.md b/test/generators/markdown/Class.mutually'.md index 29ba8fab85..3b00c21b8b 100644 --- a/test/generators/markdown/Class.mutually'.md +++ b/test/generators/markdown/Class.mutually'.md @@ -2,4 +2,4 @@ Class mutually' -Class Class.mutually' \ No newline at end of file +Class `Class.mutually'` \ No newline at end of file diff --git a/test/generators/markdown/Class.polymorphic'.md b/test/generators/markdown/Class.polymorphic'.md index dbc1c394d5..fc222f0fcd 100644 --- a/test/generators/markdown/Class.polymorphic'.md +++ b/test/generators/markdown/Class.polymorphic'.md @@ -2,4 +2,4 @@ Class polymorphic' -Class Class.polymorphic' \ No newline at end of file +Class `Class.polymorphic'` \ No newline at end of file diff --git a/test/generators/markdown/Class.recursive'.md b/test/generators/markdown/Class.recursive'.md index 117d8e5984..0ce70ddcb9 100644 --- a/test/generators/markdown/Class.recursive'.md +++ b/test/generators/markdown/Class.recursive'.md @@ -2,4 +2,4 @@ Class recursive' -Class Class.recursive' \ No newline at end of file +Class `Class.recursive'` \ No newline at end of file diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md index 0195935424..09df98011f 100644 --- a/test/generators/markdown/External.md +++ b/test/generators/markdown/External.md @@ -1,6 +1,6 @@ External -Module External +Module `External` diff --git a/test/generators/markdown/Functor.F1.argument-1-Arg.md b/test/generators/markdown/Functor.F1.argument-1-Arg.md index 8133c65efd..87466ccdc8 100644 --- a/test/generators/markdown/Functor.F1.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F1.argument-1-Arg.md @@ -4,7 +4,7 @@ F1 1-Arg -Parameter F1.1-Arg +Parameter `F1.1-Arg` diff --git a/test/generators/markdown/Functor.F1.md b/test/generators/markdown/Functor.F1.md index 78297ce6ed..5a0fbfb033 100644 --- a/test/generators/markdown/Functor.F1.md +++ b/test/generators/markdown/Functor.F1.md @@ -2,7 +2,7 @@ Functor F1 -Module Functor.F1 +Module `Functor.F1` # Parameters diff --git a/test/generators/markdown/Functor.F2.argument-1-Arg.md b/test/generators/markdown/Functor.F2.argument-1-Arg.md index 895c3fdcbb..0aa6e67c42 100644 --- a/test/generators/markdown/Functor.F2.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F2.argument-1-Arg.md @@ -4,7 +4,7 @@ F2 1-Arg -Parameter F2.1-Arg +Parameter `F2.1-Arg` diff --git a/test/generators/markdown/Functor.F2.md b/test/generators/markdown/Functor.F2.md index af71f9c680..89d9208f3f 100644 --- a/test/generators/markdown/Functor.F2.md +++ b/test/generators/markdown/Functor.F2.md @@ -2,7 +2,7 @@ Functor F2 -Module Functor.F2 +Module `Functor.F2` # Parameters diff --git a/test/generators/markdown/Functor.F3.argument-1-Arg.md b/test/generators/markdown/Functor.F3.argument-1-Arg.md index a993e0b519..e1cf8e8980 100644 --- a/test/generators/markdown/Functor.F3.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F3.argument-1-Arg.md @@ -4,7 +4,7 @@ F3 1-Arg -Parameter F3.1-Arg +Parameter `F3.1-Arg` diff --git a/test/generators/markdown/Functor.F3.md b/test/generators/markdown/Functor.F3.md index 83123a8670..4747896ec8 100644 --- a/test/generators/markdown/Functor.F3.md +++ b/test/generators/markdown/Functor.F3.md @@ -2,7 +2,7 @@ Functor F3 -Module Functor.F3 +Module `Functor.F3` # Parameters diff --git a/test/generators/markdown/Functor.F4.argument-1-Arg.md b/test/generators/markdown/Functor.F4.argument-1-Arg.md index 69b55399ec..98e5cd207c 100644 --- a/test/generators/markdown/Functor.F4.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F4.argument-1-Arg.md @@ -4,7 +4,7 @@ F4 1-Arg -Parameter F4.1-Arg +Parameter `F4.1-Arg` diff --git a/test/generators/markdown/Functor.F4.md b/test/generators/markdown/Functor.F4.md index e72e2c0e1a..df2ab891fa 100644 --- a/test/generators/markdown/Functor.F4.md +++ b/test/generators/markdown/Functor.F4.md @@ -2,7 +2,7 @@ Functor F4 -Module Functor.F4 +Module `Functor.F4` # Parameters diff --git a/test/generators/markdown/Functor.F5.md b/test/generators/markdown/Functor.F5.md index f1b6403f87..4033906922 100644 --- a/test/generators/markdown/Functor.F5.md +++ b/test/generators/markdown/Functor.F5.md @@ -2,7 +2,7 @@ Functor F5 -Module Functor.F5 +Module `Functor.F5` # Parameters diff --git a/test/generators/markdown/Functor.md b/test/generators/markdown/Functor.md index bb16940272..b80f8b9757 100644 --- a/test/generators/markdown/Functor.md +++ b/test/generators/markdown/Functor.md @@ -1,6 +1,6 @@ Functor -Module Functor +Module `Functor` diff --git a/test/generators/markdown/Functor.module-type-S.md b/test/generators/markdown/Functor.module-type-S.md index cb4e417959..b7de7ea78a 100644 --- a/test/generators/markdown/Functor.module-type-S.md +++ b/test/generators/markdown/Functor.module-type-S.md @@ -2,7 +2,7 @@ Functor S -Module type Functor.S +Module type `Functor.S` diff --git a/test/generators/markdown/Functor.module-type-S1.argument-1-_.md b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md index 8c5c46f3b0..17485b9375 100644 --- a/test/generators/markdown/Functor.module-type-S1.argument-1-_.md +++ b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md @@ -4,7 +4,7 @@ S1 1-_ -Parameter S1.1-_ +Parameter `S1.1-_` diff --git a/test/generators/markdown/Functor.module-type-S1.md b/test/generators/markdown/Functor.module-type-S1.md index c31ae63a25..80dafac2b0 100644 --- a/test/generators/markdown/Functor.module-type-S1.md +++ b/test/generators/markdown/Functor.module-type-S1.md @@ -2,7 +2,7 @@ Functor S1 -Module type Functor.S1 +Module type `Functor.S1` # Parameters diff --git a/test/generators/markdown/Functor2.X.argument-1-Y.md b/test/generators/markdown/Functor2.X.argument-1-Y.md index 13f784fce9..1ce8ac974e 100644 --- a/test/generators/markdown/Functor2.X.argument-1-Y.md +++ b/test/generators/markdown/Functor2.X.argument-1-Y.md @@ -4,7 +4,7 @@ X 1-Y -Parameter X.1-Y +Parameter `X.1-Y` diff --git a/test/generators/markdown/Functor2.X.argument-2-Z.md b/test/generators/markdown/Functor2.X.argument-2-Z.md index 17dbb5f697..34ddf9bfc2 100644 --- a/test/generators/markdown/Functor2.X.argument-2-Z.md +++ b/test/generators/markdown/Functor2.X.argument-2-Z.md @@ -4,7 +4,7 @@ X 2-Z -Parameter X.2-Z +Parameter `X.2-Z` diff --git a/test/generators/markdown/Functor2.X.md b/test/generators/markdown/Functor2.X.md index ffc40681d3..11478923bf 100644 --- a/test/generators/markdown/Functor2.X.md +++ b/test/generators/markdown/Functor2.X.md @@ -2,7 +2,7 @@ Functor2 X -Module Functor2.X +Module `Functor2.X` # Parameters diff --git a/test/generators/markdown/Functor2.md b/test/generators/markdown/Functor2.md index 184809e944..8cce76edf2 100644 --- a/test/generators/markdown/Functor2.md +++ b/test/generators/markdown/Functor2.md @@ -1,6 +1,6 @@ Functor2 -Module Functor2 +Module `Functor2` diff --git a/test/generators/markdown/Functor2.module-type-S.md b/test/generators/markdown/Functor2.module-type-S.md index 2021592466..21b1fcb87f 100644 --- a/test/generators/markdown/Functor2.module-type-S.md +++ b/test/generators/markdown/Functor2.module-type-S.md @@ -2,7 +2,7 @@ Functor2 S -Module type Functor2.S +Module type `Functor2.S` diff --git a/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md b/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md index 6ff792ac2b..65b39521cf 100644 --- a/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md +++ b/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md @@ -4,7 +4,7 @@ XF 1-Y -Parameter XF.1-Y +Parameter `XF.1-Y` diff --git a/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md b/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md index 35ecf8495f..3f8789aa9f 100644 --- a/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md +++ b/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md @@ -4,7 +4,7 @@ XF 2-Z -Parameter XF.2-Z +Parameter `XF.2-Z` diff --git a/test/generators/markdown/Functor2.module-type-XF.md b/test/generators/markdown/Functor2.module-type-XF.md index 42f1542955..0cc97253fa 100644 --- a/test/generators/markdown/Functor2.module-type-XF.md +++ b/test/generators/markdown/Functor2.module-type-XF.md @@ -2,7 +2,7 @@ Functor2 XF -Module type Functor2.XF +Module type `Functor2.XF` # Parameters diff --git a/test/generators/markdown/Include.md b/test/generators/markdown/Include.md index 2a3617f0a8..f501f79229 100644 --- a/test/generators/markdown/Include.md +++ b/test/generators/markdown/Include.md @@ -1,6 +1,6 @@ Include -Module Include +Module `Include` diff --git a/test/generators/markdown/Include.module-type-Dorminant_Module.md b/test/generators/markdown/Include.module-type-Dorminant_Module.md index 0a1686d4ec..f9f4f29313 100644 --- a/test/generators/markdown/Include.module-type-Dorminant_Module.md +++ b/test/generators/markdown/Include.module-type-Dorminant_Module.md @@ -2,7 +2,7 @@ Include Dorminant_Module -Module type Include.Dorminant_Module +Module type `Include.Dorminant_Module` diff --git a/test/generators/markdown/Include.module-type-Inherent_Module.md b/test/generators/markdown/Include.module-type-Inherent_Module.md index c2ca674158..4e10a48489 100644 --- a/test/generators/markdown/Include.module-type-Inherent_Module.md +++ b/test/generators/markdown/Include.module-type-Inherent_Module.md @@ -2,7 +2,7 @@ Include Inherent_Module -Module type Include.Inherent_Module +Module type `Include.Inherent_Module` diff --git a/test/generators/markdown/Include.module-type-Inlined.md b/test/generators/markdown/Include.module-type-Inlined.md index 420f9567a5..45194f8982 100644 --- a/test/generators/markdown/Include.module-type-Inlined.md +++ b/test/generators/markdown/Include.module-type-Inlined.md @@ -2,7 +2,7 @@ Include Inlined -Module type Include.Inlined +Module type `Include.Inlined` diff --git a/test/generators/markdown/Include.module-type-Not_inlined.md b/test/generators/markdown/Include.module-type-Not_inlined.md index 391c80c31e..5736e3aeaa 100644 --- a/test/generators/markdown/Include.module-type-Not_inlined.md +++ b/test/generators/markdown/Include.module-type-Not_inlined.md @@ -2,7 +2,7 @@ Include Not_inlined -Module type Include.Not_inlined +Module type `Include.Not_inlined` diff --git a/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md b/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md index 1505118984..fe207ddde5 100644 --- a/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md +++ b/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md @@ -2,7 +2,7 @@ Include Not_inlined_and_closed -Module type Include.Not_inlined_and_closed +Module type `Include.Not_inlined_and_closed` diff --git a/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md b/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md index d1f94edc0b..e739980268 100644 --- a/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md +++ b/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md @@ -2,7 +2,7 @@ Include Not_inlined_and_opened -Module type Include.Not_inlined_and_opened +Module type `Include.Not_inlined_and_opened` diff --git a/test/generators/markdown/Include2.X.md b/test/generators/markdown/Include2.X.md index 5c413acd96..e20e4ef5e6 100644 --- a/test/generators/markdown/Include2.X.md +++ b/test/generators/markdown/Include2.X.md @@ -2,7 +2,7 @@ Include2 X -Module Include2.X +Module `Include2.X` Comment about X that should not appear when including X below. diff --git a/test/generators/markdown/Include2.Y.md b/test/generators/markdown/Include2.Y.md index 34b679e4a1..83cefa7611 100644 --- a/test/generators/markdown/Include2.Y.md +++ b/test/generators/markdown/Include2.Y.md @@ -2,7 +2,7 @@ Include2 Y -Module Include2.Y +Module `Include2.Y` Top-comment of Y. diff --git a/test/generators/markdown/Include2.Y_include_doc.md b/test/generators/markdown/Include2.Y_include_doc.md index b2db9e7887..fe24c3343b 100644 --- a/test/generators/markdown/Include2.Y_include_doc.md +++ b/test/generators/markdown/Include2.Y_include_doc.md @@ -2,7 +2,7 @@ Include2 Y_include_doc -Module Include2.Y_include_doc +Module `Include2.Y_include_doc` diff --git a/test/generators/markdown/Include2.Y_include_synopsis.md b/test/generators/markdown/Include2.Y_include_synopsis.md index ffb495f05e..67210eeb9c 100644 --- a/test/generators/markdown/Include2.Y_include_synopsis.md +++ b/test/generators/markdown/Include2.Y_include_synopsis.md @@ -2,9 +2,9 @@ Include2 Y_include_synopsis -Module Include2.Y_include_synopsis +Module `Include2.Y_include_synopsis` -The include Y below should have the synopsis from Y 's top-comment attached to it. +The `include Y` below should have the synopsis from `Y` 's top-comment attached to it. diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index f8c21355a6..b3a360f8d4 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -1,6 +1,6 @@ Include2 -Module Include2 +Module `Include2` diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index fa9c50a56f..39094738b3 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -1,6 +1,6 @@ Include_sections -Module Include_sections +Module `Include_sections` @@ -8,7 +8,7 @@ Module Include_sections A module type. -Let's include [Something](Include_sections.module-type-Something.md) once +Let's include [`Something`](Include_sections.module-type-Something.md) once # Something 1 @@ -24,7 +24,7 @@ Some text. # Second include -Let's include [Something](Include_sections.module-type-Something.md) a second time: the heading level should be shift here. +Let's include [`Something`](Include_sections.module-type-Something.md) a second time: the heading level should be shift here. # Something 1 diff --git a/test/generators/markdown/Include_sections.module-type-Something.md b/test/generators/markdown/Include_sections.module-type-Something.md index 9e05d40fbf..08f695af62 100644 --- a/test/generators/markdown/Include_sections.module-type-Something.md +++ b/test/generators/markdown/Include_sections.module-type-Something.md @@ -2,7 +2,7 @@ Include_sections Something -Module type Include_sections.Something +Module type `Include_sections.Something` A module type. diff --git a/test/generators/markdown/Interlude.md b/test/generators/markdown/Interlude.md index c583931174..d1f99495f0 100644 --- a/test/generators/markdown/Interlude.md +++ b/test/generators/markdown/Interlude.md @@ -1,6 +1,6 @@ Interlude -Module Interlude +Module `Interlude` This is the comment associated to the module. diff --git a/test/generators/markdown/Labels.A.md b/test/generators/markdown/Labels.A.md index 18762d29e9..e8377618a1 100644 --- a/test/generators/markdown/Labels.A.md +++ b/test/generators/markdown/Labels.A.md @@ -2,6 +2,6 @@ Labels A -Module Labels.A +Module `Labels.A` # Attached to module \ No newline at end of file diff --git a/test/generators/markdown/Labels.c.md b/test/generators/markdown/Labels.c.md index 8993888182..c47ed42384 100644 --- a/test/generators/markdown/Labels.c.md +++ b/test/generators/markdown/Labels.c.md @@ -2,6 +2,6 @@ Labels c -Class Labels.c +Class `Labels.c` # Attached to class \ No newline at end of file diff --git a/test/generators/markdown/Labels.class-type-cs.md b/test/generators/markdown/Labels.class-type-cs.md index 66f0675cf4..dfa7735e31 100644 --- a/test/generators/markdown/Labels.class-type-cs.md +++ b/test/generators/markdown/Labels.class-type-cs.md @@ -2,6 +2,6 @@ Labels cs -Class type Labels.cs +Class type `Labels.cs` # Attached to class type \ No newline at end of file diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index 7d19dc0e1e..491e6eaa51 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -1,6 +1,6 @@ Labels -Module Labels +Module `Labels` # Attached to unit diff --git a/test/generators/markdown/Labels.module-type-S.md b/test/generators/markdown/Labels.module-type-S.md index d528b3a0f2..414dc21d03 100644 --- a/test/generators/markdown/Labels.module-type-S.md +++ b/test/generators/markdown/Labels.module-type-S.md @@ -2,6 +2,6 @@ Labels S -Module type Labels.S +Module type `Labels.S` # Attached to module type \ No newline at end of file diff --git a/test/generators/markdown/Markup.X.md b/test/generators/markdown/Markup.X.md index e1610e9022..35c6b00818 100644 --- a/test/generators/markdown/Markup.X.md +++ b/test/generators/markdown/Markup.X.md @@ -2,4 +2,4 @@ Markup X -Module Markup.X \ No newline at end of file +Module `Markup.X` \ No newline at end of file diff --git a/test/generators/markdown/Markup.Y.md b/test/generators/markdown/Markup.Y.md index 7671336ac5..1c3c0d9459 100644 --- a/test/generators/markdown/Markup.Y.md +++ b/test/generators/markdown/Markup.Y.md @@ -2,4 +2,4 @@ Markup Y -Module Markup.Y \ No newline at end of file +Module `Markup.Y` \ No newline at end of file diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 3cbf16e470..cd25993b91 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -1,6 +1,6 @@ Markup -Module Markup +Module `Markup` Here, we test the rendering of comment markup. @@ -46,19 +46,19 @@ This paragraph has some styled elements: **bold** and _italic_ , **_bold italic_ Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ emphasis_ is rendered in italics._ _It also work the same in [links in italics with _emphasis _in_ emphasis_ .](#)_ -code is a different kind of markup that doesn't allow nested markup. +`code` is a different kind of markup that doesn't allow nested markup. It's possible for two markup elements to appear **next** _to_ each other and have a space, and appear **next** _to_ each other with no space. It doesn't matter **how** _much_ space it was in the source: in this sentence, it was two space characters. And in this one, there is **a** _newline_ . -This is also true between _non-_ code markup _and_ code . +This is also true between _non-_ `code` markup _and_ `code` . -Code can appear **inside other markup** . Its display shouldn't be affected. +Code can appear **inside `other` markup** . Its display shouldn't be affected. # Links and references -This is a [link](#) . It sends you to the top of this page. Links can have markup inside them: [**bold**](#) , [_italics_](#) , [_emphasis_](#) , [super script](#) , [sub script](#) , and [code](#) . Links can also be nested _[inside](#)_ markup. Links cannot be nested inside each other. This link has no replacement text: [#](#) . The text is filled in by odoc. This is a shorthand link: [#](#) . The text is also filled in by odoc in this case. +This is a [link](#) . It sends you to the top of this page. Links can have markup inside them: [**bold**](#) , [_italics_](#) , [_emphasis_](#) , [super script](#) , [sub script](#) , and [`code`](#) . Links can also be nested _[inside](#)_ markup. Links cannot be nested inside each other. This link has no replacement text: [#](#) . The text is filled in by odoc. This is a shorthand link: [#](#) . The text is also filled in by odoc in this case. -This is a reference to [foo](#val-foo) . References can have replacement text: [the value foo](#val-foo) . Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: [**bold**](#val-foo) , [_italic_](#val-foo) , [_emphasis_](#val-foo) , [super script](#val-foo) , [sub script](#val-foo) , and [code](#val-foo) . It's also possible to surround a reference in a style: **[foo](#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 [`foo`](#val-foo) . References can have replacement text: [the value foo](#val-foo) . Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: [**bold**](#val-foo) , [_italic_](#val-foo) , [_emphasis_](#val-foo) , [super script](#val-foo) , [sub script](#val-foo) , and [`code`](#val-foo) . It's also possible to surround a reference in a style: **[`foo`](#val-foo)** . References can't be nested inside references, and links and references can't be nested inside each other. # Preformatted text @@ -114,7 +114,7 @@ just creates a paragraph outside the list. - and can include references - - [foo](#val-foo) + - [`foo`](#val-foo) # Unicode @@ -133,11 +133,11 @@ Raw HTML can be as inline elements in # Modules -@[X](Markup.X.md): +@[`X`](Markup.X.md): -@[X](Markup.X.md): +@[`X`](Markup.X.md): -@[Y](Markup.Y.md): +@[`Y`](Markup.Y.md): # Tags @@ -155,7 +155,7 @@ Each comment can end with zero or more tags. Here are some examples: @see [#](#): -@see foo.ml: +@see `foo.ml`: @see Foo: diff --git a/test/generators/markdown/Module.M'.md b/test/generators/markdown/Module.M'.md index 550397744a..2885863222 100644 --- a/test/generators/markdown/Module.M'.md +++ b/test/generators/markdown/Module.M'.md @@ -2,4 +2,4 @@ Module M' -Module Module.M' \ No newline at end of file +Module `Module.M'` \ No newline at end of file diff --git a/test/generators/markdown/Module.Mutually.md b/test/generators/markdown/Module.Mutually.md index 374a3d93b0..2e5696a12c 100644 --- a/test/generators/markdown/Module.Mutually.md +++ b/test/generators/markdown/Module.Mutually.md @@ -2,4 +2,4 @@ Module Mutually -Module Module.Mutually \ No newline at end of file +Module `Module.Mutually` \ No newline at end of file diff --git a/test/generators/markdown/Module.Recursive.md b/test/generators/markdown/Module.Recursive.md index ea7f4018e3..74daca47f2 100644 --- a/test/generators/markdown/Module.Recursive.md +++ b/test/generators/markdown/Module.Recursive.md @@ -2,4 +2,4 @@ Module Recursive -Module Module.Recursive \ No newline at end of file +Module `Module.Recursive` \ No newline at end of file diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index b94853643b..3a8d537759 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -1,6 +1,6 @@ Module -Module Module +Module `Module` Foo. diff --git a/test/generators/markdown/Module.module-type-S.M.md b/test/generators/markdown/Module.module-type-S.M.md index 238cbef37f..55c9c052c6 100644 --- a/test/generators/markdown/Module.module-type-S.M.md +++ b/test/generators/markdown/Module.module-type-S.M.md @@ -4,4 +4,4 @@ S M -Module S.M \ No newline at end of file +Module `S.M` \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S.md b/test/generators/markdown/Module.module-type-S.md index 20c1c69b62..7fac8be3c5 100644 --- a/test/generators/markdown/Module.module-type-S.md +++ b/test/generators/markdown/Module.module-type-S.md @@ -2,7 +2,7 @@ Module S -Module type Module.S +Module type `Module.S` diff --git a/test/generators/markdown/Module.module-type-S3.M.md b/test/generators/markdown/Module.module-type-S3.M.md index 9e799a6475..ca501af660 100644 --- a/test/generators/markdown/Module.module-type-S3.M.md +++ b/test/generators/markdown/Module.module-type-S3.M.md @@ -4,4 +4,4 @@ S3 M -Module S3.M \ No newline at end of file +Module `S3.M` \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S3.md b/test/generators/markdown/Module.module-type-S3.md index 868e009fec..e931cf5ed7 100644 --- a/test/generators/markdown/Module.module-type-S3.md +++ b/test/generators/markdown/Module.module-type-S3.md @@ -2,7 +2,7 @@ Module S3 -Module type Module.S3 +Module type `Module.S3` diff --git a/test/generators/markdown/Module.module-type-S4.M.md b/test/generators/markdown/Module.module-type-S4.M.md index 4b2154399d..f774eef789 100644 --- a/test/generators/markdown/Module.module-type-S4.M.md +++ b/test/generators/markdown/Module.module-type-S4.M.md @@ -4,4 +4,4 @@ S4 M -Module S4.M \ No newline at end of file +Module `S4.M` \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S4.md b/test/generators/markdown/Module.module-type-S4.md index 90b5739bde..57c7e6eede 100644 --- a/test/generators/markdown/Module.module-type-S4.md +++ b/test/generators/markdown/Module.module-type-S4.md @@ -2,7 +2,7 @@ Module S4 -Module type Module.S4 +Module type `Module.S4` diff --git a/test/generators/markdown/Module.module-type-S5.M.md b/test/generators/markdown/Module.module-type-S5.M.md index 5edf58c4bc..5f16cdbdfd 100644 --- a/test/generators/markdown/Module.module-type-S5.M.md +++ b/test/generators/markdown/Module.module-type-S5.M.md @@ -4,4 +4,4 @@ S5 M -Module S5.M \ No newline at end of file +Module `S5.M` \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S5.md b/test/generators/markdown/Module.module-type-S5.md index cd1df21cb6..ab0e3ec09f 100644 --- a/test/generators/markdown/Module.module-type-S5.md +++ b/test/generators/markdown/Module.module-type-S5.md @@ -2,7 +2,7 @@ Module S5 -Module type Module.S5 +Module type `Module.S5` diff --git a/test/generators/markdown/Module.module-type-S6.M.md b/test/generators/markdown/Module.module-type-S6.M.md index 84e4d7f7ab..f0283d8cb3 100644 --- a/test/generators/markdown/Module.module-type-S6.M.md +++ b/test/generators/markdown/Module.module-type-S6.M.md @@ -4,4 +4,4 @@ S6 M -Module S6.M \ No newline at end of file +Module `S6.M` \ No newline at end of file diff --git a/test/generators/markdown/Module.module-type-S6.md b/test/generators/markdown/Module.module-type-S6.md index 64bd1a945f..9c82d20282 100644 --- a/test/generators/markdown/Module.module-type-S6.md +++ b/test/generators/markdown/Module.module-type-S6.md @@ -2,7 +2,7 @@ Module S6 -Module type Module.S6 +Module type `Module.S6` diff --git a/test/generators/markdown/Module.module-type-S7.md b/test/generators/markdown/Module.module-type-S7.md index 924007faa2..6254790100 100644 --- a/test/generators/markdown/Module.module-type-S7.md +++ b/test/generators/markdown/Module.module-type-S7.md @@ -2,7 +2,7 @@ Module S7 -Module type Module.S7 +Module type `Module.S7` diff --git a/test/generators/markdown/Module.module-type-S8.md b/test/generators/markdown/Module.module-type-S8.md index 4082efdf51..7bdb906059 100644 --- a/test/generators/markdown/Module.module-type-S8.md +++ b/test/generators/markdown/Module.module-type-S8.md @@ -2,7 +2,7 @@ Module S8 -Module type Module.S8 +Module type `Module.S8` diff --git a/test/generators/markdown/Module.module-type-S9.md b/test/generators/markdown/Module.module-type-S9.md index d73b88bb86..728e55f3e6 100644 --- a/test/generators/markdown/Module.module-type-S9.md +++ b/test/generators/markdown/Module.module-type-S9.md @@ -2,4 +2,4 @@ Module S9 -Module type Module.S9 \ No newline at end of file +Module type `Module.S9` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_alias.md b/test/generators/markdown/Module_type_alias.md index d5f616e8d0..54b1605993 100644 --- a/test/generators/markdown/Module_type_alias.md +++ b/test/generators/markdown/Module_type_alias.md @@ -1,6 +1,6 @@ Module_type_alias -Module Module_type_alias +Module `Module_type_alias` Module Type Aliases diff --git a/test/generators/markdown/Module_type_alias.module-type-A.md b/test/generators/markdown/Module_type_alias.module-type-A.md index 38f54c5a0d..616a565f1a 100644 --- a/test/generators/markdown/Module_type_alias.module-type-A.md +++ b/test/generators/markdown/Module_type_alias.module-type-A.md @@ -2,7 +2,7 @@ Module_type_alias A -Module type Module_type_alias.A +Module type `Module_type_alias.A` diff --git a/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md b/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md index 4f2ff51831..7658a529d8 100644 --- a/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md +++ b/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md @@ -4,7 +4,7 @@ B 1-C -Parameter B.1-C +Parameter `B.1-C` diff --git a/test/generators/markdown/Module_type_alias.module-type-B.md b/test/generators/markdown/Module_type_alias.module-type-B.md index 15d54b5c3c..2bfe7faabf 100644 --- a/test/generators/markdown/Module_type_alias.module-type-B.md +++ b/test/generators/markdown/Module_type_alias.module-type-B.md @@ -2,7 +2,7 @@ Module_type_alias B -Module type Module_type_alias.B +Module type `Module_type_alias.B` # Parameters diff --git a/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md b/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md index eb3cb558f8..a32b3fac9c 100644 --- a/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md +++ b/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md @@ -4,7 +4,7 @@ E 1-F -Parameter E.1-F +Parameter `E.1-F` diff --git a/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md b/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md index 0b64fb5c68..73fd867bbc 100644 --- a/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md +++ b/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md @@ -4,7 +4,7 @@ E 2-C -Parameter E.2-C +Parameter `E.2-C` diff --git a/test/generators/markdown/Module_type_alias.module-type-E.md b/test/generators/markdown/Module_type_alias.module-type-E.md index 8aac6c36e1..aacddc9031 100644 --- a/test/generators/markdown/Module_type_alias.module-type-E.md +++ b/test/generators/markdown/Module_type_alias.module-type-E.md @@ -2,7 +2,7 @@ Module_type_alias E -Module type Module_type_alias.E +Module type `Module_type_alias.E` # Parameters diff --git a/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md b/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md index 89ce922b41..f7f64f136c 100644 --- a/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md +++ b/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md @@ -4,7 +4,7 @@ G 1-H -Parameter G.1-H +Parameter `G.1-H` diff --git a/test/generators/markdown/Module_type_alias.module-type-G.md b/test/generators/markdown/Module_type_alias.module-type-G.md index c6806b5e3e..6c8aeb4d2d 100644 --- a/test/generators/markdown/Module_type_alias.module-type-G.md +++ b/test/generators/markdown/Module_type_alias.module-type-G.md @@ -2,7 +2,7 @@ Module_type_alias G -Module type Module_type_alias.G +Module type `Module_type_alias.G` # Parameters diff --git a/test/generators/markdown/Module_type_subst.Basic.md b/test/generators/markdown/Module_type_subst.Basic.md index 734fd96a11..092813d26f 100644 --- a/test/generators/markdown/Module_type_subst.Basic.md +++ b/test/generators/markdown/Module_type_subst.Basic.md @@ -2,7 +2,7 @@ Module_type_subst Basic -Module Module_type_subst.Basic +Module `Module_type_subst.Basic` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md index 648f235fde..0ea28f8a5b 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md @@ -6,4 +6,4 @@ a M -Module a.M \ No newline at end of file +Module `a.M` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-a.md b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md index 686474eb3b..73918989a9 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md @@ -4,7 +4,7 @@ Basic a -Module type Basic.a +Module type `Basic.a` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md index 1fb1f73299..159056b5d9 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md @@ -6,4 +6,4 @@ c M -Module c.M \ No newline at end of file +Module `c.M` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-c.md b/test/generators/markdown/Module_type_subst.Basic.module-type-c.md index a945120bc4..bab3b0b873 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-c.md @@ -4,7 +4,7 @@ Basic c -Module type Basic.c +Module type `Basic.c` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md index 2ca2303d9b..26a86fb815 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md @@ -4,7 +4,7 @@ Basic u -Module type Basic.u +Module type `Basic.u` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md index 08317bf3b5..aa83b60587 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md @@ -6,4 +6,4 @@ u T -Module type u.T \ No newline at end of file +Module type `u.T` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md index 674e50e124..a6ad0b5a60 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md @@ -6,4 +6,4 @@ u2 M -Module u2.M \ No newline at end of file +Module `u2.M` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md index 73677bfe06..faf31b6423 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md @@ -4,7 +4,7 @@ Basic u2 -Module type Basic.u2 +Module type `Basic.u2` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md index 71e89f2532..40af069288 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md @@ -6,4 +6,4 @@ u2 T -Module type u2.T \ No newline at end of file +Module type `u2.T` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md index 21ae5e5c3c..1e0362847b 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_.md @@ -4,7 +4,7 @@ Basic with_ -Module type Basic.with_ +Module type `Basic.with_` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md index 7219c05c96..fba608ead9 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md @@ -6,4 +6,4 @@ with_2 M -Module with_2.M \ No newline at end of file +Module `with_2.M` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md index 6ad00afb5e..5ce3116017 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md @@ -4,7 +4,7 @@ Basic with_2 -Module type Basic.with_2 +Module type `Basic.with_2` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md index 471745a3ed..6a99e90bff 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md @@ -6,4 +6,4 @@ with_2 T -Module type with_2.T \ No newline at end of file +Module type `with_2.T` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Local.md b/test/generators/markdown/Module_type_subst.Local.md index 5f20e8922d..177bf1ef4e 100644 --- a/test/generators/markdown/Module_type_subst.Local.md +++ b/test/generators/markdown/Module_type_subst.Local.md @@ -2,7 +2,7 @@ Module_type_subst Local -Module Module_type_subst.Local +Module `Module_type_subst.Local` diff --git a/test/generators/markdown/Module_type_subst.Local.module-type-local.md b/test/generators/markdown/Module_type_subst.Local.module-type-local.md index 9f307328dc..3ddbb6d3cd 100644 --- a/test/generators/markdown/Module_type_subst.Local.module-type-local.md +++ b/test/generators/markdown/Module_type_subst.Local.module-type-local.md @@ -4,7 +4,7 @@ Local local -Module type Local.local +Module type `Local.local` diff --git a/test/generators/markdown/Module_type_subst.Local.module-type-s.md b/test/generators/markdown/Module_type_subst.Local.module-type-s.md index 4373a29658..1b0d16738b 100644 --- a/test/generators/markdown/Module_type_subst.Local.module-type-s.md +++ b/test/generators/markdown/Module_type_subst.Local.module-type-s.md @@ -4,4 +4,4 @@ Local s -Module type Local.s \ No newline at end of file +Module type `Local.s` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.md b/test/generators/markdown/Module_type_subst.Nested.md index 212fd0e912..d23cc8c13f 100644 --- a/test/generators/markdown/Module_type_subst.Nested.md +++ b/test/generators/markdown/Module_type_subst.Nested.md @@ -2,7 +2,7 @@ Module_type_subst Nested -Module Module_type_subst.Nested +Module `Module_type_subst.Nested` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md index 7657eeb234..12de1c48d0 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md @@ -6,7 +6,7 @@ nested N -Module nested.N +Module `nested.N` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md index c65192e1a7..d84158036a 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md @@ -8,4 +8,4 @@ N t -Module type N.t \ No newline at end of file +Module type `N.t` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md index f2920570d3..a09a44ef2e 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md @@ -4,7 +4,7 @@ Nested nested -Module type Nested.nested +Module type `Nested.nested` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md index 4132fb2089..2114ab6f4f 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.N.md @@ -6,7 +6,7 @@ with_ N -Module with_.N +Module `with_.N` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md index 1c2b457152..04a206a65b 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md @@ -4,7 +4,7 @@ Nested with_ -Module type Nested.with_ +Module type `Nested.with_` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md index 83beb9f3e0..20a4a766c9 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md @@ -6,4 +6,4 @@ with_subst N -Module with_subst.N \ No newline at end of file +Module `with_subst.N` \ No newline at end of file diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md index a34e5dab1f..6e26782142 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md @@ -4,7 +4,7 @@ Nested with_subst -Module type Nested.with_subst +Module type `Nested.with_subst` diff --git a/test/generators/markdown/Module_type_subst.Structural.md b/test/generators/markdown/Module_type_subst.Structural.md index 46195b2618..ece362070a 100644 --- a/test/generators/markdown/Module_type_subst.Structural.md +++ b/test/generators/markdown/Module_type_subst.Structural.md @@ -2,7 +2,7 @@ Module_type_subst Structural -Module Module_type_subst.Structural +Module `Module_type_subst.Structural` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md index 984293f679..a3758f71a1 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md @@ -4,7 +4,7 @@ Structural u -Module type Structural.u +Module type `Structural.u` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md index ea06df5d9d..3fe7ebbe2a 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md @@ -6,7 +6,7 @@ u a -Module type u.a +Module type `u.a` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md index fbae4ccea5..2f5d401940 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md @@ -8,7 +8,7 @@ a b -Module type a.b +Module type `a.b` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md index 53557518bb..516a3d6020 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md @@ -10,7 +10,7 @@ b c -Module type b.c +Module type `b.c` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md index 06d74e7c1b..6cb288647c 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md @@ -4,7 +4,7 @@ Structural w -Module type Structural.w +Module type `Structural.w` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md index 81e23a97d1..8340939ff5 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md @@ -6,7 +6,7 @@ w a -Module type w.a +Module type `w.a` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md index 5902db4242..ad16ec0e5a 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md @@ -8,7 +8,7 @@ a b -Module type a.b +Module type `a.b` diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md index 57a7ec6519..d6687ef073 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md @@ -10,7 +10,7 @@ b c -Module type b.c +Module type `b.c` diff --git a/test/generators/markdown/Module_type_subst.md b/test/generators/markdown/Module_type_subst.md index cab0e249c1..01a5d2ccdf 100644 --- a/test/generators/markdown/Module_type_subst.md +++ b/test/generators/markdown/Module_type_subst.md @@ -1,6 +1,6 @@ Module_type_subst -Module Module_type_subst +Module `Module_type_subst` diff --git a/test/generators/markdown/Module_type_subst.module-type-s.md b/test/generators/markdown/Module_type_subst.module-type-s.md index 1d0b8502df..874df212cc 100644 --- a/test/generators/markdown/Module_type_subst.module-type-s.md +++ b/test/generators/markdown/Module_type_subst.module-type-s.md @@ -2,4 +2,4 @@ Module_type_subst s -Module type Module_type_subst.s \ No newline at end of file +Module type `Module_type_subst.s` \ No newline at end of file diff --git a/test/generators/markdown/Nested.F.argument-1-Arg1.md b/test/generators/markdown/Nested.F.argument-1-Arg1.md index 9a7e3f93dc..f645466571 100644 --- a/test/generators/markdown/Nested.F.argument-1-Arg1.md +++ b/test/generators/markdown/Nested.F.argument-1-Arg1.md @@ -4,7 +4,7 @@ F 1-Arg1 -Parameter F.1-Arg1 +Parameter `F.1-Arg1` # Type diff --git a/test/generators/markdown/Nested.F.argument-2-Arg2.md b/test/generators/markdown/Nested.F.argument-2-Arg2.md index d653476a01..71f423a5a2 100644 --- a/test/generators/markdown/Nested.F.argument-2-Arg2.md +++ b/test/generators/markdown/Nested.F.argument-2-Arg2.md @@ -4,7 +4,7 @@ F 2-Arg2 -Parameter F.2-Arg2 +Parameter `F.2-Arg2` # Type diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md index 3aaee73f28..f47b5f8f95 100644 --- a/test/generators/markdown/Nested.F.md +++ b/test/generators/markdown/Nested.F.md @@ -2,7 +2,7 @@ Nested F -Module Nested.F +Module `Nested.F` This is a functor F. diff --git a/test/generators/markdown/Nested.X.md b/test/generators/markdown/Nested.X.md index 5411347c6a..cb5d138815 100644 --- a/test/generators/markdown/Nested.X.md +++ b/test/generators/markdown/Nested.X.md @@ -2,7 +2,7 @@ Nested X -Module Nested.X +Module `Nested.X` This is module X. diff --git a/test/generators/markdown/Nested.inherits.md b/test/generators/markdown/Nested.inherits.md index 815d77cf95..4101a530cb 100644 --- a/test/generators/markdown/Nested.inherits.md +++ b/test/generators/markdown/Nested.inherits.md @@ -2,7 +2,7 @@ Nested inherits -Class Nested.inherits +Class `Nested.inherits` diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md index 82a838a8e9..17be89ce16 100644 --- a/test/generators/markdown/Nested.md +++ b/test/generators/markdown/Nested.md @@ -1,6 +1,6 @@ Nested -Module Nested +Module `Nested` This comment needs to be here before #235 is fixed. diff --git a/test/generators/markdown/Nested.module-type-Y.md b/test/generators/markdown/Nested.module-type-Y.md index 258ac10da4..6e494e2ff9 100644 --- a/test/generators/markdown/Nested.module-type-Y.md +++ b/test/generators/markdown/Nested.module-type-Y.md @@ -2,7 +2,7 @@ Nested Y -Module type Nested.Y +Module type `Nested.Y` This is module type Y. diff --git a/test/generators/markdown/Nested.z.md b/test/generators/markdown/Nested.z.md index f8117cf8b1..9dd6f1871f 100644 --- a/test/generators/markdown/Nested.z.md +++ b/test/generators/markdown/Nested.z.md @@ -2,7 +2,7 @@ Nested z -Class Nested.z +Class `Nested.z` This is class z. diff --git a/test/generators/markdown/Ocamlary.Aliases.E.md b/test/generators/markdown/Ocamlary.Aliases.E.md index 50d2823062..ace7d0c8fd 100644 --- a/test/generators/markdown/Ocamlary.Aliases.E.md +++ b/test/generators/markdown/Ocamlary.Aliases.E.md @@ -4,7 +4,7 @@ Aliases E -Module Aliases.E +Module `Aliases.E` diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.A.md b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md index ec75ea14dc..87d781cb70 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.A.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md @@ -6,7 +6,7 @@ Foo A -Module Foo.A +Module `Foo.A` diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.B.md b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md index ed7af4df80..2be08e4b19 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.B.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md @@ -6,7 +6,7 @@ Foo B -Module Foo.B +Module `Foo.B` diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.C.md b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md index 9a692943db..ea481ca3cd 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.C.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md @@ -6,7 +6,7 @@ Foo C -Module Foo.C +Module `Foo.C` diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.D.md b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md index f0b4d0856c..eae02160e4 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.D.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md @@ -6,7 +6,7 @@ Foo D -Module Foo.D +Module `Foo.D` diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.E.md b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md index e5f3335b55..24a0c4aa27 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.E.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md @@ -6,7 +6,7 @@ Foo E -Module Foo.E +Module `Foo.E` diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.md b/test/generators/markdown/Ocamlary.Aliases.Foo.md index 249a41ef1f..eb08b56ee0 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.md @@ -4,7 +4,7 @@ Aliases Foo -Module Aliases.Foo +Module `Aliases.Foo` diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.Y.md b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md index 7d3cdc6d2b..20bf3b3873 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P1.Y.md +++ b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md @@ -6,7 +6,7 @@ P1 Y -Module P1.Y +Module `P1.Y` diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.md b/test/generators/markdown/Ocamlary.Aliases.P1.md index 32d6c464c7..c1de46c7b7 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P1.md +++ b/test/generators/markdown/Ocamlary.Aliases.P1.md @@ -4,7 +4,7 @@ Aliases P1 -Module Aliases.P1 +Module `Aliases.P1` diff --git a/test/generators/markdown/Ocamlary.Aliases.P2.md b/test/generators/markdown/Ocamlary.Aliases.P2.md index 3237d3de13..c01a3c4d96 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P2.md +++ b/test/generators/markdown/Ocamlary.Aliases.P2.md @@ -4,7 +4,7 @@ Aliases P2 -Module Aliases.P2 +Module `Aliases.P2` diff --git a/test/generators/markdown/Ocamlary.Aliases.Std.md b/test/generators/markdown/Ocamlary.Aliases.Std.md index cd9eb9c163..c848f095da 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Std.md +++ b/test/generators/markdown/Ocamlary.Aliases.Std.md @@ -4,7 +4,7 @@ Aliases Std -Module Aliases.Std +Module `Aliases.Std` diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index fd2137c3db..23365f4b08 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -2,7 +2,7 @@ Ocamlary Aliases -Module Ocamlary.Aliases +Module `Ocamlary.Aliases` Let's imitate jst's layout. @@ -64,7 +64,7 @@ Let's imitate jst's layout. --- -Just for giggle, let's see what happens when we include [Foo](Ocamlary.Aliases.Foo.md) . +Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases.Foo.md) . @@ -105,7 +105,7 @@ Just for giggle, let's see what happens when we include [Foo](Ocamlary.Aliases.F > [A.t](Ocamlary.Aliases.Foo.A.md#type-t) -And also, let's refer to [A.t](Ocamlary.Aliases.Foo.A.md#type-t) and [Foo.B.id](Ocamlary.Aliases.Foo.B.md#val-id) +And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and [`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) diff --git a/test/generators/markdown/Ocamlary.Buffer.md b/test/generators/markdown/Ocamlary.Buffer.md index f808f3cb96..0d5f754ac7 100644 --- a/test/generators/markdown/Ocamlary.Buffer.md +++ b/test/generators/markdown/Ocamlary.Buffer.md @@ -2,9 +2,9 @@ Ocamlary Buffer -Module Ocamlary.Buffer +Module `Ocamlary.Buffer` -References are resolved after everything, so {!Buffer.t} won't resolve. +References are resolved after everything, so `{!Buffer.t}` won't resolve. diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md index 095521c60f..98e87d9297 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md @@ -6,7 +6,7 @@ Base List -Module Base.List +Module `Base.List` diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md index 098cbf6612..9a892d9e89 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md @@ -4,7 +4,7 @@ CanonicalTest Base -Module CanonicalTest.Base +Module `CanonicalTest.Base` diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md index 0b028a1208..81a06fa09a 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.C.md @@ -6,7 +6,7 @@ Base_Tests C -Module Base_Tests.C +Module `Base_Tests.C` diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md index 54d43b3179..e6dbd2dc8f 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md @@ -4,7 +4,7 @@ CanonicalTest Base_Tests -Module CanonicalTest.Base_Tests +Module `CanonicalTest.Base_Tests` diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md index 78e99d0b43..54b237ef50 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md @@ -4,7 +4,7 @@ CanonicalTest List_modif -Module CanonicalTest.List_modif +Module `CanonicalTest.List_modif` diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.md b/test/generators/markdown/Ocamlary.CanonicalTest.md index fb70bd64b4..de4edcfe70 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.md @@ -2,7 +2,7 @@ Ocamlary CanonicalTest -Module Ocamlary.CanonicalTest +Module `Ocamlary.CanonicalTest` diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md index b30db9b8b2..3c601438e3 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index 0a2e862ef5..a29e12793e 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -4,9 +4,9 @@ CollectionModule InnerModuleA -Module CollectionModule.InnerModuleA +Module `CollectionModule.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index 182eddd512..ff0c7b4494 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md index 169ea86fcb..513df6db4d 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.md @@ -2,9 +2,9 @@ Ocamlary CollectionModule -Module Ocamlary.CollectionModule +Module `Ocamlary.CollectionModule` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md index f3034432cc..99888d067a 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md @@ -8,7 +8,7 @@ Y c -Class Y.c +Class `Y.c` diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.md index 0fea5ce7ab..7410030cdb 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md @@ -6,7 +6,7 @@ X Y -Module X.Y +Module `X.Y` diff --git a/test/generators/markdown/Ocamlary.Dep1.X.md b/test/generators/markdown/Ocamlary.Dep1.X.md index 582fb90d84..73d8eb8d32 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.md @@ -4,7 +4,7 @@ Dep1 X -Module Dep1.X +Module `Dep1.X` diff --git a/test/generators/markdown/Ocamlary.Dep1.md b/test/generators/markdown/Ocamlary.Dep1.md index 16bbce007a..b10cb0e737 100644 --- a/test/generators/markdown/Ocamlary.Dep1.md +++ b/test/generators/markdown/Ocamlary.Dep1.md @@ -2,7 +2,7 @@ Ocamlary Dep1 -Module Ocamlary.Dep1 +Module `Ocamlary.Dep1` diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md index 8314f9e07c..4941ed0cd5 100644 --- a/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md @@ -6,7 +6,7 @@ S c -Class S.c +Class `S.c` diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md index e8ccdaf4af..10894be264 100644 --- a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md @@ -4,7 +4,7 @@ Dep1 S -Module type Dep1.S +Module type `Dep1.S` diff --git a/test/generators/markdown/Ocamlary.Dep11.md b/test/generators/markdown/Ocamlary.Dep11.md index 5e163d7858..64aab282b7 100644 --- a/test/generators/markdown/Ocamlary.Dep11.md +++ b/test/generators/markdown/Ocamlary.Dep11.md @@ -2,7 +2,7 @@ Ocamlary Dep11 -Module Ocamlary.Dep11 +Module `Ocamlary.Dep11` diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md index e9c13f0e3d..9adea9048d 100644 --- a/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md @@ -6,7 +6,7 @@ S c -Class S.c +Class `S.c` diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md index 3e392705b3..9e7d57161b 100644 --- a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md @@ -4,7 +4,7 @@ Dep11 S -Module type Dep11.S +Module type `Dep11.S` diff --git a/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md index 43d9817e56..100b34a796 100644 --- a/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md @@ -4,7 +4,7 @@ Dep12 1-Arg -Parameter Dep12.1-Arg +Parameter `Dep12.1-Arg` diff --git a/test/generators/markdown/Ocamlary.Dep12.md b/test/generators/markdown/Ocamlary.Dep12.md index 1bdf6011bc..07a58e1440 100644 --- a/test/generators/markdown/Ocamlary.Dep12.md +++ b/test/generators/markdown/Ocamlary.Dep12.md @@ -2,7 +2,7 @@ Ocamlary Dep12 -Module Ocamlary.Dep12 +Module `Ocamlary.Dep12` # Parameters diff --git a/test/generators/markdown/Ocamlary.Dep13.c.md b/test/generators/markdown/Ocamlary.Dep13.c.md index 6d5500ff9e..bba9294892 100644 --- a/test/generators/markdown/Ocamlary.Dep13.c.md +++ b/test/generators/markdown/Ocamlary.Dep13.c.md @@ -4,7 +4,7 @@ Dep13 c -Class Dep13.c +Class `Dep13.c` diff --git a/test/generators/markdown/Ocamlary.Dep13.md b/test/generators/markdown/Ocamlary.Dep13.md index f54fd53492..6a9d1cb8f7 100644 --- a/test/generators/markdown/Ocamlary.Dep13.md +++ b/test/generators/markdown/Ocamlary.Dep13.md @@ -2,7 +2,7 @@ Ocamlary Dep13 -Module Ocamlary.Dep13 +Module `Ocamlary.Dep13` diff --git a/test/generators/markdown/Ocamlary.Dep2.A.md b/test/generators/markdown/Ocamlary.Dep2.A.md index c89104328f..b50ab08dad 100644 --- a/test/generators/markdown/Ocamlary.Dep2.A.md +++ b/test/generators/markdown/Ocamlary.Dep2.A.md @@ -4,7 +4,7 @@ Dep2 A -Module Dep2.A +Module `Dep2.A` diff --git a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md index 1ddafd4b60..8050458429 100644 --- a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md +++ b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.X.md @@ -6,7 +6,7 @@ Dep2 X -Module 1-Arg.X +Module `1-Arg.X` diff --git a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md index cc9e652959..3ad389d8d8 100644 --- a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md @@ -4,7 +4,7 @@ Dep2 1-Arg -Parameter Dep2.1-Arg +Parameter `Dep2.1-Arg` diff --git a/test/generators/markdown/Ocamlary.Dep2.md b/test/generators/markdown/Ocamlary.Dep2.md index beb8e747a0..095372b534 100644 --- a/test/generators/markdown/Ocamlary.Dep2.md +++ b/test/generators/markdown/Ocamlary.Dep2.md @@ -2,7 +2,7 @@ Ocamlary Dep2 -Module Ocamlary.Dep2 +Module `Ocamlary.Dep2` # Parameters diff --git a/test/generators/markdown/Ocamlary.Dep3.md b/test/generators/markdown/Ocamlary.Dep3.md index c4d518ccf8..fd9c860f9b 100644 --- a/test/generators/markdown/Ocamlary.Dep3.md +++ b/test/generators/markdown/Ocamlary.Dep3.md @@ -2,7 +2,7 @@ Ocamlary Dep3 -Module Ocamlary.Dep3 +Module `Ocamlary.Dep3` diff --git a/test/generators/markdown/Ocamlary.Dep4.X.md b/test/generators/markdown/Ocamlary.Dep4.X.md index ecee81f307..f95cbafc40 100644 --- a/test/generators/markdown/Ocamlary.Dep4.X.md +++ b/test/generators/markdown/Ocamlary.Dep4.X.md @@ -4,7 +4,7 @@ Dep4 X -Module Dep4.X +Module `Dep4.X` diff --git a/test/generators/markdown/Ocamlary.Dep4.md b/test/generators/markdown/Ocamlary.Dep4.md index 2468d3a333..8f82a81314 100644 --- a/test/generators/markdown/Ocamlary.Dep4.md +++ b/test/generators/markdown/Ocamlary.Dep4.md @@ -2,7 +2,7 @@ Ocamlary Dep4 -Module Ocamlary.Dep4 +Module `Ocamlary.Dep4` diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md index 9aa42c078e..a778fb7dfe 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md @@ -6,7 +6,7 @@ S X -Module S.X +Module `S.X` diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md index b3829b6343..843925a23d 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md @@ -6,4 +6,4 @@ S Y -Module S.Y \ No newline at end of file +Module `S.Y` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md index 256e735650..75f4802ab0 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md @@ -4,7 +4,7 @@ Dep4 S -Module type Dep4.S +Module type `Dep4.S` diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-T.md b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md index 63dc0895bb..a7250f0401 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md @@ -4,7 +4,7 @@ Dep4 T -Module type Dep4.T +Module type `Dep4.T` diff --git a/test/generators/markdown/Ocamlary.Dep5.Z.md b/test/generators/markdown/Ocamlary.Dep5.Z.md index 23f6e00b9e..b08bcf3164 100644 --- a/test/generators/markdown/Ocamlary.Dep5.Z.md +++ b/test/generators/markdown/Ocamlary.Dep5.Z.md @@ -4,7 +4,7 @@ Dep5 Z -Module Dep5.Z +Module `Dep5.Z` diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md index 44f3ffe5c2..fbc8e3593f 100644 --- a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md @@ -4,7 +4,7 @@ Dep5 1-Arg -Parameter Dep5.1-Arg +Parameter `Dep5.1-Arg` diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md index 5253ca7eb9..62343408d0 100644 --- a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md @@ -8,4 +8,4 @@ S Y -Module S.Y \ No newline at end of file +Module `S.Y` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md index a8762bb080..4635dcf4dd 100644 --- a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md @@ -6,7 +6,7 @@ Dep5 S -Module type 1-Arg.S +Module type `1-Arg.S` diff --git a/test/generators/markdown/Ocamlary.Dep5.md b/test/generators/markdown/Ocamlary.Dep5.md index 623ed61601..f5e3b09afc 100644 --- a/test/generators/markdown/Ocamlary.Dep5.md +++ b/test/generators/markdown/Ocamlary.Dep5.md @@ -2,7 +2,7 @@ Ocamlary Dep5 -Module Ocamlary.Dep5 +Module `Ocamlary.Dep5` # Parameters diff --git a/test/generators/markdown/Ocamlary.Dep6.X.Y.md b/test/generators/markdown/Ocamlary.Dep6.X.Y.md index 8922e5decb..910317d232 100644 --- a/test/generators/markdown/Ocamlary.Dep6.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep6.X.Y.md @@ -6,7 +6,7 @@ X Y -Module X.Y +Module `X.Y` diff --git a/test/generators/markdown/Ocamlary.Dep6.X.md b/test/generators/markdown/Ocamlary.Dep6.X.md index 7cd7db9fb3..c0f2ab0ad2 100644 --- a/test/generators/markdown/Ocamlary.Dep6.X.md +++ b/test/generators/markdown/Ocamlary.Dep6.X.md @@ -4,7 +4,7 @@ Dep6 X -Module Dep6.X +Module `Dep6.X` diff --git a/test/generators/markdown/Ocamlary.Dep6.md b/test/generators/markdown/Ocamlary.Dep6.md index 775bfad917..6cb8c97389 100644 --- a/test/generators/markdown/Ocamlary.Dep6.md +++ b/test/generators/markdown/Ocamlary.Dep6.md @@ -2,7 +2,7 @@ Ocamlary Dep6 -Module Ocamlary.Dep6 +Module `Ocamlary.Dep6` diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-S.md b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md index d7afe17198..a355f2ebde 100644 --- a/test/generators/markdown/Ocamlary.Dep6.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md @@ -4,7 +4,7 @@ Dep6 S -Module type Dep6.S +Module type `Dep6.S` diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md index 4de9efa353..d92b4bff39 100644 --- a/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md @@ -6,7 +6,7 @@ T Y -Module T.Y +Module `T.Y` diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-T.md b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md index a811d8ca99..868c99b550 100644 --- a/test/generators/markdown/Ocamlary.Dep6.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md @@ -4,7 +4,7 @@ Dep6 T -Module type Dep6.T +Module type `Dep6.T` diff --git a/test/generators/markdown/Ocamlary.Dep7.M.md b/test/generators/markdown/Ocamlary.Dep7.M.md index f402995f3a..d4e1b37396 100644 --- a/test/generators/markdown/Ocamlary.Dep7.M.md +++ b/test/generators/markdown/Ocamlary.Dep7.M.md @@ -4,7 +4,7 @@ Dep7 M -Module Dep7.M +Module `Dep7.M` diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md index 69b47295be..21de9aec43 100644 --- a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md @@ -6,7 +6,7 @@ Dep7 X -Module 1-Arg.X +Module `1-Arg.X` diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md index 1599ed9b6e..ebe3ce17ab 100644 --- a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md @@ -4,7 +4,7 @@ Dep7 1-Arg -Parameter Dep7.1-Arg +Parameter `Dep7.1-Arg` diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md index 6767e2cbcd..8f5c1b5f5b 100644 --- a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md @@ -6,7 +6,7 @@ Dep7 T -Module type 1-Arg.T +Module type `1-Arg.T` diff --git a/test/generators/markdown/Ocamlary.Dep7.md b/test/generators/markdown/Ocamlary.Dep7.md index 62eff030e6..12ed805ed2 100644 --- a/test/generators/markdown/Ocamlary.Dep7.md +++ b/test/generators/markdown/Ocamlary.Dep7.md @@ -2,7 +2,7 @@ Ocamlary Dep7 -Module Ocamlary.Dep7 +Module `Ocamlary.Dep7` # Parameters diff --git a/test/generators/markdown/Ocamlary.Dep8.md b/test/generators/markdown/Ocamlary.Dep8.md index a4e2a4d7aa..bc16e30e6d 100644 --- a/test/generators/markdown/Ocamlary.Dep8.md +++ b/test/generators/markdown/Ocamlary.Dep8.md @@ -2,7 +2,7 @@ Ocamlary Dep8 -Module Ocamlary.Dep8 +Module `Ocamlary.Dep8` diff --git a/test/generators/markdown/Ocamlary.Dep8.module-type-T.md b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md index 73d02b2e63..b0503be7fd 100644 --- a/test/generators/markdown/Ocamlary.Dep8.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md @@ -4,7 +4,7 @@ Dep8 T -Module type Dep8.T +Module type `Dep8.T` diff --git a/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md index 0c8256fdc2..db8de153b8 100644 --- a/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md +++ b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md @@ -4,7 +4,7 @@ Dep9 1-X -Parameter Dep9.1-X +Parameter `Dep9.1-X` diff --git a/test/generators/markdown/Ocamlary.Dep9.md b/test/generators/markdown/Ocamlary.Dep9.md index 9d83e8e7da..e332087cd6 100644 --- a/test/generators/markdown/Ocamlary.Dep9.md +++ b/test/generators/markdown/Ocamlary.Dep9.md @@ -2,7 +2,7 @@ Ocamlary Dep9 -Module Ocamlary.Dep9 +Module `Ocamlary.Dep9` # Parameters diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md index 90b4535241..18b37a76a2 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md @@ -4,7 +4,7 @@ DoubleInclude1 DoubleInclude2 -Module DoubleInclude1.DoubleInclude2 +Module `DoubleInclude1.DoubleInclude2` diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.md b/test/generators/markdown/Ocamlary.DoubleInclude1.md index 2cf4fc8739..1775e53383 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude1.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.md @@ -2,7 +2,7 @@ Ocamlary DoubleInclude1 -Module Ocamlary.DoubleInclude1 +Module `Ocamlary.DoubleInclude1` diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md index 7feb228ffd..f32c869e85 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md @@ -4,7 +4,7 @@ DoubleInclude3 DoubleInclude2 -Module DoubleInclude3.DoubleInclude2 +Module `DoubleInclude3.DoubleInclude2` diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.md b/test/generators/markdown/Ocamlary.DoubleInclude3.md index b73bb98157..dbfffbf149 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude3.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.md @@ -2,7 +2,7 @@ Ocamlary DoubleInclude3 -Module Ocamlary.DoubleInclude3 +Module `Ocamlary.DoubleInclude3` diff --git a/test/generators/markdown/Ocamlary.Empty.md b/test/generators/markdown/Ocamlary.Empty.md index dbd3e2ae87..8a1672f5c7 100644 --- a/test/generators/markdown/Ocamlary.Empty.md +++ b/test/generators/markdown/Ocamlary.Empty.md @@ -2,7 +2,7 @@ Ocamlary Empty -Module Ocamlary.Empty +Module `Ocamlary.Empty` A plain, empty module diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md index 3db554831e..8bc2180e52 100644 --- a/test/generators/markdown/Ocamlary.ExtMod.md +++ b/test/generators/markdown/Ocamlary.ExtMod.md @@ -2,7 +2,7 @@ Ocamlary ExtMod -Module Ocamlary.ExtMod +Module `Ocamlary.ExtMod` diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md index 18abdde669..286f7ab1e2 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md index d171368bc7..fdbd083364 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -6,9 +6,9 @@ FunctorTypeOf InnerModuleA -Module 1-Collection.InnerModuleA +Module `1-Collection.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md index 2d5a9488f3..d293d0dbc5 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md index 9a45809591..a2478c400e 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -4,9 +4,9 @@ FunctorTypeOf 1-Collection -Parameter FunctorTypeOf.1-Collection +Parameter `FunctorTypeOf.1-Collection` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md index 0574b2cae0..d44365e14f 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md @@ -2,9 +2,9 @@ Ocamlary FunctorTypeOf -Module Ocamlary.FunctorTypeOf +Module `Ocamlary.FunctorTypeOf` -This comment is for FunctorTypeOf . +This comment is for `FunctorTypeOf` . # Parameters diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md index 43753b9f79..3f40d2cd27 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md @@ -4,4 +4,4 @@ IncludeInclude1 IncludeInclude2_M -Module IncludeInclude1.IncludeInclude2_M \ No newline at end of file +Module `IncludeInclude1.IncludeInclude2_M` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md index 45b5e251c5..f302249027 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -2,7 +2,7 @@ Ocamlary IncludeInclude1 -Module Ocamlary.IncludeInclude1 +Module `Ocamlary.IncludeInclude1` diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md index c20838d37e..0591c40d25 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md @@ -4,7 +4,7 @@ IncludeInclude1 IncludeInclude2 -Module type IncludeInclude1.IncludeInclude2 +Module type `IncludeInclude1.IncludeInclude2` diff --git a/test/generators/markdown/Ocamlary.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md index a48c6d18ce..803d19b7eb 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude2_M.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md @@ -2,4 +2,4 @@ Ocamlary IncludeInclude2_M -Module Ocamlary.IncludeInclude2_M \ No newline at end of file +Module `Ocamlary.IncludeInclude2_M` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.IncludedA.md b/test/generators/markdown/Ocamlary.IncludedA.md index 6f794c6a70..5fe2f42c9f 100644 --- a/test/generators/markdown/Ocamlary.IncludedA.md +++ b/test/generators/markdown/Ocamlary.IncludedA.md @@ -2,7 +2,7 @@ Ocamlary IncludedA -Module Ocamlary.IncludedA +Module `Ocamlary.IncludedA` diff --git a/test/generators/markdown/Ocamlary.M.md b/test/generators/markdown/Ocamlary.M.md index 1aa0479608..2a892a6028 100644 --- a/test/generators/markdown/Ocamlary.M.md +++ b/test/generators/markdown/Ocamlary.M.md @@ -2,7 +2,7 @@ Ocamlary M -Module Ocamlary.M +Module `Ocamlary.M` diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md index d5f31458c5..e36fcb80c3 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignature.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md @@ -2,6 +2,6 @@ Ocamlary ModuleWithSignature -Module Ocamlary.ModuleWithSignature +Module `Ocamlary.ModuleWithSignature` -A plain module of a signature of [EmptySig](Ocamlary.module-type-EmptySig.md) (reference) \ No newline at end of file +A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md index 64ba31e2b6..ebd0fee282 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md @@ -2,7 +2,7 @@ Ocamlary ModuleWithSignatureAlias -Module Ocamlary.ModuleWithSignatureAlias +Module `Ocamlary.ModuleWithSignatureAlias` A plain module with an alias signature diff --git a/test/generators/markdown/Ocamlary.One.md b/test/generators/markdown/Ocamlary.One.md index 28d023ceab..0d8f1cace6 100644 --- a/test/generators/markdown/Ocamlary.One.md +++ b/test/generators/markdown/Ocamlary.One.md @@ -2,7 +2,7 @@ Ocamlary One -Module Ocamlary.One +Module `Ocamlary.One` diff --git a/test/generators/markdown/Ocamlary.Only_a_module.md b/test/generators/markdown/Ocamlary.Only_a_module.md index 26f8ca3170..fa68b44672 100644 --- a/test/generators/markdown/Ocamlary.Only_a_module.md +++ b/test/generators/markdown/Ocamlary.Only_a_module.md @@ -2,7 +2,7 @@ Ocamlary Only_a_module -Module Ocamlary.Only_a_module +Module `Ocamlary.Only_a_module` diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md index 6d17d441a7..4ee0d4f694 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index 417bcba684..7783aa0cf6 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -4,9 +4,9 @@ Recollection InnerModuleA -Module Recollection.InnerModuleA +Module `Recollection.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md index 9a592a26e2..dc61ff7732 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md index 85e838fea5..3587e5e3cf 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md index caa22b50f6..775ecd56ed 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -6,9 +6,9 @@ Recollection InnerModuleA -Module 1-C.InnerModuleA +Module `1-C.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md index ad7c1a59aa..f66011c775 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md index 39c226bc3d..5d64ca4381 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -4,9 +4,9 @@ Recollection 1-C -Parameter Recollection.1-C +Parameter `Recollection.1-C` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md index 9438cde94b..0d4663606c 100644 --- a/test/generators/markdown/Ocamlary.Recollection.md +++ b/test/generators/markdown/Ocamlary.Recollection.md @@ -2,7 +2,7 @@ Ocamlary Recollection -Module Ocamlary.Recollection +Module `Ocamlary.Recollection` # Parameters @@ -12,7 +12,7 @@ Module Ocamlary.Recollection # Signature -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.With10.md b/test/generators/markdown/Ocamlary.With10.md index a73e8696bb..532c4567fb 100644 --- a/test/generators/markdown/Ocamlary.With10.md +++ b/test/generators/markdown/Ocamlary.With10.md @@ -2,7 +2,7 @@ Ocamlary With10 -Module Ocamlary.With10 +Module `Ocamlary.With10` diff --git a/test/generators/markdown/Ocamlary.With10.module-type-T.M.md b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md index 2cb0c59d24..c87488c24c 100644 --- a/test/generators/markdown/Ocamlary.With10.module-type-T.M.md +++ b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md @@ -6,7 +6,7 @@ T M -Module T.M +Module `T.M` diff --git a/test/generators/markdown/Ocamlary.With10.module-type-T.md b/test/generators/markdown/Ocamlary.With10.module-type-T.md index 2cf73cf727..0f4bcff60e 100644 --- a/test/generators/markdown/Ocamlary.With10.module-type-T.md +++ b/test/generators/markdown/Ocamlary.With10.module-type-T.md @@ -4,9 +4,9 @@ With10 T -Module type With10.T +Module type `With10.T` -[With10.T]() is a submodule type. +[`With10.T`]() is a submodule type. diff --git a/test/generators/markdown/Ocamlary.With2.md b/test/generators/markdown/Ocamlary.With2.md index 9613440ceb..7ab42eda63 100644 --- a/test/generators/markdown/Ocamlary.With2.md +++ b/test/generators/markdown/Ocamlary.With2.md @@ -2,7 +2,7 @@ Ocamlary With2 -Module Ocamlary.With2 +Module `Ocamlary.With2` diff --git a/test/generators/markdown/Ocamlary.With2.module-type-S.md b/test/generators/markdown/Ocamlary.With2.module-type-S.md index d6bf61978b..4b8308c52d 100644 --- a/test/generators/markdown/Ocamlary.With2.module-type-S.md +++ b/test/generators/markdown/Ocamlary.With2.module-type-S.md @@ -4,7 +4,7 @@ With2 S -Module type With2.S +Module type `With2.S` diff --git a/test/generators/markdown/Ocamlary.With3.N.md b/test/generators/markdown/Ocamlary.With3.N.md index 2676d57b2d..d79b2635bb 100644 --- a/test/generators/markdown/Ocamlary.With3.N.md +++ b/test/generators/markdown/Ocamlary.With3.N.md @@ -4,7 +4,7 @@ With3 N -Module With3.N +Module `With3.N` diff --git a/test/generators/markdown/Ocamlary.With3.md b/test/generators/markdown/Ocamlary.With3.md index c427e59fe3..26c0d7d0a5 100644 --- a/test/generators/markdown/Ocamlary.With3.md +++ b/test/generators/markdown/Ocamlary.With3.md @@ -2,7 +2,7 @@ Ocamlary With3 -Module Ocamlary.With3 +Module `Ocamlary.With3` diff --git a/test/generators/markdown/Ocamlary.With4.N.md b/test/generators/markdown/Ocamlary.With4.N.md index 436d5db654..ff57122e36 100644 --- a/test/generators/markdown/Ocamlary.With4.N.md +++ b/test/generators/markdown/Ocamlary.With4.N.md @@ -4,7 +4,7 @@ With4 N -Module With4.N +Module `With4.N` diff --git a/test/generators/markdown/Ocamlary.With4.md b/test/generators/markdown/Ocamlary.With4.md index a087fca5c0..e33f59c2e5 100644 --- a/test/generators/markdown/Ocamlary.With4.md +++ b/test/generators/markdown/Ocamlary.With4.md @@ -2,7 +2,7 @@ Ocamlary With4 -Module Ocamlary.With4 +Module `Ocamlary.With4` diff --git a/test/generators/markdown/Ocamlary.With5.N.md b/test/generators/markdown/Ocamlary.With5.N.md index 92e61b553e..500f8022ae 100644 --- a/test/generators/markdown/Ocamlary.With5.N.md +++ b/test/generators/markdown/Ocamlary.With5.N.md @@ -4,7 +4,7 @@ With5 N -Module With5.N +Module `With5.N` diff --git a/test/generators/markdown/Ocamlary.With5.md b/test/generators/markdown/Ocamlary.With5.md index b2850b6a21..8f95d99cbd 100644 --- a/test/generators/markdown/Ocamlary.With5.md +++ b/test/generators/markdown/Ocamlary.With5.md @@ -2,7 +2,7 @@ Ocamlary With5 -Module Ocamlary.With5 +Module `Ocamlary.With5` diff --git a/test/generators/markdown/Ocamlary.With5.module-type-S.md b/test/generators/markdown/Ocamlary.With5.module-type-S.md index 3c7746f9f5..18ded1cb75 100644 --- a/test/generators/markdown/Ocamlary.With5.module-type-S.md +++ b/test/generators/markdown/Ocamlary.With5.module-type-S.md @@ -4,7 +4,7 @@ With5 S -Module type With5.S +Module type `With5.S` diff --git a/test/generators/markdown/Ocamlary.With6.md b/test/generators/markdown/Ocamlary.With6.md index c0f3f14627..0947fca610 100644 --- a/test/generators/markdown/Ocamlary.With6.md +++ b/test/generators/markdown/Ocamlary.With6.md @@ -2,7 +2,7 @@ Ocamlary With6 -Module Ocamlary.With6 +Module `Ocamlary.With6` diff --git a/test/generators/markdown/Ocamlary.With6.module-type-T.M.md b/test/generators/markdown/Ocamlary.With6.module-type-T.M.md index 42ec1ce89b..0f731431a4 100644 --- a/test/generators/markdown/Ocamlary.With6.module-type-T.M.md +++ b/test/generators/markdown/Ocamlary.With6.module-type-T.M.md @@ -6,7 +6,7 @@ T M -Module T.M +Module `T.M` diff --git a/test/generators/markdown/Ocamlary.With6.module-type-T.md b/test/generators/markdown/Ocamlary.With6.module-type-T.md index efaa2742eb..ec902a93fa 100644 --- a/test/generators/markdown/Ocamlary.With6.module-type-T.md +++ b/test/generators/markdown/Ocamlary.With6.module-type-T.md @@ -4,7 +4,7 @@ With6 T -Module type With6.T +Module type `With6.T` diff --git a/test/generators/markdown/Ocamlary.With7.argument-1-X.md b/test/generators/markdown/Ocamlary.With7.argument-1-X.md index 127791ee26..168e444e24 100644 --- a/test/generators/markdown/Ocamlary.With7.argument-1-X.md +++ b/test/generators/markdown/Ocamlary.With7.argument-1-X.md @@ -4,7 +4,7 @@ With7 1-X -Parameter With7.1-X +Parameter `With7.1-X` diff --git a/test/generators/markdown/Ocamlary.With7.md b/test/generators/markdown/Ocamlary.With7.md index ff77dec191..d57061bf13 100644 --- a/test/generators/markdown/Ocamlary.With7.md +++ b/test/generators/markdown/Ocamlary.With7.md @@ -2,7 +2,7 @@ Ocamlary With7 -Module Ocamlary.With7 +Module `Ocamlary.With7` # Parameters diff --git a/test/generators/markdown/Ocamlary.With9.md b/test/generators/markdown/Ocamlary.With9.md index a9fd24a946..c711c30739 100644 --- a/test/generators/markdown/Ocamlary.With9.md +++ b/test/generators/markdown/Ocamlary.With9.md @@ -2,7 +2,7 @@ Ocamlary With9 -Module Ocamlary.With9 +Module `Ocamlary.With9` diff --git a/test/generators/markdown/Ocamlary.With9.module-type-S.md b/test/generators/markdown/Ocamlary.With9.module-type-S.md index 37661fa885..dab1202597 100644 --- a/test/generators/markdown/Ocamlary.With9.module-type-S.md +++ b/test/generators/markdown/Ocamlary.With9.module-type-S.md @@ -4,7 +4,7 @@ With9 S -Module type With9.S +Module type `With9.S` diff --git a/test/generators/markdown/Ocamlary.empty_class.md b/test/generators/markdown/Ocamlary.empty_class.md index b9d8c41c91..f709ae0824 100644 --- a/test/generators/markdown/Ocamlary.empty_class.md +++ b/test/generators/markdown/Ocamlary.empty_class.md @@ -2,4 +2,4 @@ Ocamlary empty_class -Class Ocamlary.empty_class \ No newline at end of file +Class `Ocamlary.empty_class` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 9e716a0e19..b6cd3cb5e6 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -1,6 +1,6 @@ Ocamlary -Module Ocamlary +Module `Ocamlary` This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: @@ -52,13 +52,13 @@ This is some verbatim text: Here is some raw LaTeX: $e^{i\pi} = -1$ -Here is an index table of Empty modules: +Here is an index table of `Empty` modules: -@[Empty](Ocamlary.Empty.md): A plain, empty module +@[`Empty`](Ocamlary.Empty.md): A plain, empty module -@[EmptyAlias](Ocamlary.Empty.md): A plain module alias of Empty +@[`EmptyAlias`](Ocamlary.Empty.md): A plain module alias of `Empty` -Odoc doesn't support {!indexlist} . +Odoc doesn't support `{!indexlist}` . Here is some superscript: x 2 @@ -66,7 +66,7 @@ Here is some subscript: x 0 Here are some escaped brackets: { [ @ ] } -Here is some _emphasis_ followed by code . +Here is some _emphasis_ `followed by code` . An unassociated comment @@ -162,7 +162,7 @@ There's a signature in a module in this signature. ###### module type [SuperSig](Ocamlary.module-type-SuperSig.md) -For a good time, see [subSig](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or [subSig](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or [SuperSig.EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) . Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is the section and [EmptySig](Ocamlary.module-type-EmptySig.md) is the module signature. +For a good time, see [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or [`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) . Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module signature. @@ -480,13 +480,13 @@ This comment is for `IncludeModuleType` -######    field1 : int ; +######    `;int : field1` This comment is for `field1` -######    field2 : int ; +######    `;int : field2` This comment is for `field2` @@ -500,19 +500,19 @@ This comment is for `record`This comment is also for `record` -######    mutable a : int ; +######    `;int : a mutable` `a` -######    b : unit ; +######    `;unit : b` `b` -######    mutable c : int ; +######    `;int : c mutable` `c` @@ -564,11 +564,11 @@ This comment is for `variant`This comment is also for `variant` -######    | `TagA +######    `| ` `` `TagA `` -######    | `ConstrB of int +######    `| ` `` int of `ConstrB `` ] @@ -660,11 +660,11 @@ This comment is for `variant_alias` -######    field1 : int ; +######    `;int : field1` -######    field2 : int ; +######    `;int : field2` } @@ -676,11 +676,11 @@ This comment is for `record_alias` -######    | [poly_variant](#type-poly_variant) +######    `| ` [poly_variant](#type-poly_variant) -######    | `TagC +######    `| ` `` `TagC `` ] @@ -692,7 +692,7 @@ This comment is for `poly_variant_union` -######    | `TagA of 'a +######    `| ` `` 'a of `TagA `` ] @@ -702,11 +702,11 @@ This comment is for `poly_variant_union` -######    | `TagA of 'a +######    `| ` `` 'a of `TagA `` -######    | `ConstrB of 'b +######    `| ` `` 'b of `ConstrB `` ] @@ -765,19 +765,19 @@ This comment is for `poly_variant_union` -######    | `A +######    `| ` `` `A `` -######    | `B of [ `B1 | `B2 ] +######    `| ` `` [ `B1 | `B2 ] of `B `` -######    | `C +######    `| ` `` `C `` -######    | `D of [ `D1 of [ `D1a ] ] +######    `| ` `` [ [ `D1a ] of`D1 ] of `D `` ] @@ -1256,19 +1256,19 @@ With ocamldoc, toplevel units will be linked and documented, while submodules wi With odoc, everything should be resolved (and linked) but only toplevel units will be documented. -@[Dep1.X](Ocamlary.Dep1.X.md): +@[`Dep1.X`](Ocamlary.Dep1.X.md): -@[Ocamlary.IncludeInclude1](Ocamlary.IncludeInclude1.md): +@[`Ocamlary.IncludeInclude1`](Ocamlary.IncludeInclude1.md): -@[Ocamlary](): This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: +@[`Ocamlary`](): This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: ### Weirder usages involving module types --- -@[IncludeInclude1.IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md): +@[`IncludeInclude1.IncludeInclude2_M`](Ocamlary.IncludeInclude1.IncludeInclude2_M.md): -@[Dep4.X](Ocamlary.Dep4.X.md): +@[`Dep4.X`](Ocamlary.Dep4.X.md): # Playing with @canonical paths @@ -1276,7 +1276,7 @@ With odoc, everything should be resolved (and linked) but only toplevel units wi ###### module [CanonicalTest](Ocamlary.CanonicalTest.md) -Some ref to [CanonicalTest.Base_Tests.C.t](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) and [CanonicalTest.Base_Tests.L.id](Ocamlary.CanonicalTest.Base.List.md#val-id) . But also to [CanonicalTest.Base.List](Ocamlary.CanonicalTest.Base.List.md) and [CanonicalTest.Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +Some ref to [`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) and [`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id) . But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) # Aliases again @@ -1290,25 +1290,25 @@ Let's imitate jst's layout. I can refer to -- {!section:indexmodules} : [Trying the {!modules: ...} command.](#indexmodules) +- `{!section:indexmodules}` : [Trying the {!modules: ...} command.](#indexmodules) -- {!aliases} : [Aliases again](#aliases) +- `{!aliases}` : [Aliases again](#aliases) But also to things in submodules: -- {!section:SuperSig.SubSigA.subSig} : [subSig](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{!section:SuperSig.SubSigA.subSig}` : [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) -- {!Aliases.incl} : [incl](Ocamlary.Aliases.md#incl) +- `{!Aliases.incl}` : [`incl`](Ocamlary.Aliases.md#incl) And just to make sure we do not mess up: -- {{!section:indexmodules}A} : [A](#indexmodules) +- `{{!section:indexmodules}A}` : [A](#indexmodules) -- {{!aliases}B} : [B](#aliases) +- `{{!aliases}B}` : [B](#aliases) -- {{!section:SuperSig.SubSigA.subSig}C} : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{{!section:SuperSig.SubSigA.subSig}C}` : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) -- {{!Aliases.incl}D} : [D](Ocamlary.Aliases.md#incl) +- `{{!Aliases.incl}D}` : [D](Ocamlary.Aliases.md#incl) # New reference syntax @@ -1322,21 +1322,21 @@ And just to make sure we do not mess up: Here goes: -- {!module-M.t} : [M.t](Ocamlary.M.md#type-t) +- `{!module-M.t}` : [`M.t`](Ocamlary.M.md#type-t) -- {!module-type-M.t} : [M.t](Ocamlary.module-type-M.md#type-t) +- `{!module-type-M.t}` : [`M.t`](Ocamlary.module-type-M.md#type-t) ###### module [Only_a_module](Ocamlary.Only_a_module.md) -- {!Only_a_module.t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) +- `{!Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- {!module-Only_a_module.t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- {!module-Only_a_module.type-t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.type-t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- {!type:Only_a_module.t} : [Only_a_module.t](Ocamlary.Only_a_module.md#type-t) +- `{!type:Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md index 9b892baf6f..e2517b74df 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md index 593082d1c3..8eef35af00 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -6,9 +6,9 @@ Q InnerModuleA -Module Q.InnerModuleA +Module `Q.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index 4c60aac560..d021fdb7de 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.md b/test/generators/markdown/Ocamlary.module-type-A.Q.md index ae035a834f..447e15f771 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.md @@ -4,9 +4,9 @@ A Q -Module A.Q +Module `A.Q` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.md b/test/generators/markdown/Ocamlary.module-type-A.md index c0dacd95fe..6ff3746430 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.md +++ b/test/generators/markdown/Ocamlary.module-type-A.md @@ -2,7 +2,7 @@ Ocamlary A -Module type Ocamlary.A +Module type `Ocamlary.A` diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md index dc4874b532..08ebddbcf7 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md index 71ee07169e..7401e10c45 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -6,9 +6,9 @@ Q InnerModuleA -Module Q.InnerModuleA +Module `Q.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index 4aca417865..aeadf5c54f 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.md b/test/generators/markdown/Ocamlary.module-type-B.Q.md index 6c0c5601ee..3c90e28914 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.md @@ -4,9 +4,9 @@ B Q -Module B.Q +Module `B.Q` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.md b/test/generators/markdown/Ocamlary.module-type-B.md index 7e1c0ab058..c8df57a356 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.md +++ b/test/generators/markdown/Ocamlary.module-type-B.md @@ -2,7 +2,7 @@ Ocamlary B -Module type Ocamlary.B +Module type `Ocamlary.B` diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md index 9c2b069abe..d0faa21524 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md index bfc93bae57..98009f6ac0 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -6,9 +6,9 @@ Q InnerModuleA -Module Q.InnerModuleA +Module `Q.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index e15036d239..fec1083325 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.md b/test/generators/markdown/Ocamlary.module-type-C.Q.md index e33aca87bb..5ff528cc9b 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.md @@ -4,9 +4,9 @@ C Q -Module C.Q +Module `C.Q` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.md b/test/generators/markdown/Ocamlary.module-type-C.md index 61fd6eff45..fa87d25802 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.md +++ b/test/generators/markdown/Ocamlary.module-type-C.md @@ -2,13 +2,13 @@ Ocamlary C -Module type Ocamlary.C +Module type `Ocamlary.C` This module type includes two signatures. -- it includes [A](Ocamlary.module-type-A.md) +- it includes [`A`](Ocamlary.module-type-A.md) -- it includes [B](Ocamlary.module-type-B.md) with some substitution +- it includes [`B`](Ocamlary.module-type-B.md) with some substitution diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md index 9e1dbd7b18..8bc5f3a54f 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md index c57f5ba2e3..3d886505b3 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -4,9 +4,9 @@ COLLECTION InnerModuleA -Module COLLECTION.InnerModuleA +Module `COLLECTION.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md index dca0a0f4e7..27a79c2e34 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md index 7b223b9543..04245f46a3 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md @@ -2,11 +2,11 @@ Ocamlary COLLECTION -Module type Ocamlary.COLLECTION +Module type `Ocamlary.COLLECTION` module type of -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.module-type-Dep10.md b/test/generators/markdown/Ocamlary.module-type-Dep10.md index afcdabb14c..11e184e1af 100644 --- a/test/generators/markdown/Ocamlary.module-type-Dep10.md +++ b/test/generators/markdown/Ocamlary.module-type-Dep10.md @@ -2,7 +2,7 @@ Ocamlary Dep10 -Module type Ocamlary.Dep10 +Module type `Ocamlary.Dep10` diff --git a/test/generators/markdown/Ocamlary.module-type-Empty.md b/test/generators/markdown/Ocamlary.module-type-Empty.md index ed4eacf2c3..a339e0c43f 100644 --- a/test/generators/markdown/Ocamlary.module-type-Empty.md +++ b/test/generators/markdown/Ocamlary.module-type-Empty.md @@ -2,7 +2,7 @@ Ocamlary Empty -Module type Ocamlary.Empty +Module type `Ocamlary.Empty` An ambiguous, misnamed module type diff --git a/test/generators/markdown/Ocamlary.module-type-EmptySig.md b/test/generators/markdown/Ocamlary.module-type-EmptySig.md index 1b338cbfbd..8ef651b9fc 100644 --- a/test/generators/markdown/Ocamlary.module-type-EmptySig.md +++ b/test/generators/markdown/Ocamlary.module-type-EmptySig.md @@ -2,6 +2,6 @@ Ocamlary EmptySig -Module type Ocamlary.EmptySig +Module type `Ocamlary.EmptySig` A plain, empty module signature \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md index 07be07f04e..33a361fc40 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md @@ -2,7 +2,7 @@ Ocamlary IncludeInclude2 -Module type Ocamlary.IncludeInclude2 +Module type `Ocamlary.IncludeInclude2` diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md index b748300913..7209ceffc9 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md @@ -2,7 +2,7 @@ Ocamlary IncludeModuleType -Module type Ocamlary.IncludeModuleType +Module type `Ocamlary.IncludeModuleType` -This comment is for IncludeModuleType . +This comment is for `IncludeModuleType` . diff --git a/test/generators/markdown/Ocamlary.module-type-IncludedB.md b/test/generators/markdown/Ocamlary.module-type-IncludedB.md index 8b1c800db4..e18e984f66 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludedB.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludedB.md @@ -2,7 +2,7 @@ Ocamlary IncludedB -Module type Ocamlary.IncludedB +Module type `Ocamlary.IncludedB` diff --git a/test/generators/markdown/Ocamlary.module-type-M.md b/test/generators/markdown/Ocamlary.module-type-M.md index eb6d8b515a..4645da04fd 100644 --- a/test/generators/markdown/Ocamlary.module-type-M.md +++ b/test/generators/markdown/Ocamlary.module-type-M.md @@ -2,7 +2,7 @@ Ocamlary M -Module type Ocamlary.M +Module type `Ocamlary.M` diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md index 5a4de9a0c8..c6145d6258 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md index aff70d1add..3ec838c10f 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -6,9 +6,9 @@ C InnerModuleA -Module C.InnerModuleA +Module `C.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md index 55463e216d..8bff26b15f 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,9 +8,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.md index ddb74733cc..ee6f469cac 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.md @@ -4,9 +4,9 @@ MMM C -Module MMM.C +Module `MMM.C` -This comment is for CollectionModule . +This comment is for `CollectionModule` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.md b/test/generators/markdown/Ocamlary.module-type-MMM.md index 5749774781..578b606f82 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.md @@ -2,7 +2,7 @@ Ocamlary MMM -Module type Ocamlary.MMM +Module type `Ocamlary.MMM` diff --git a/test/generators/markdown/Ocamlary.module-type-MissingComment.md b/test/generators/markdown/Ocamlary.module-type-MissingComment.md index 2f53953731..d8f3434345 100644 --- a/test/generators/markdown/Ocamlary.module-type-MissingComment.md +++ b/test/generators/markdown/Ocamlary.module-type-MissingComment.md @@ -2,7 +2,7 @@ Ocamlary MissingComment -Module type Ocamlary.MissingComment +Module type `Ocamlary.MissingComment` An ambiguous, misnamed module type diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md index d44a7d5690..b7c0f78133 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md @@ -2,7 +2,7 @@ Ocamlary NestedInclude1 -Module type Ocamlary.NestedInclude1 +Module type `Ocamlary.NestedInclude1` diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md index 2320d51d55..8c35d8797d 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md @@ -4,7 +4,7 @@ NestedInclude1 NestedInclude2 -Module type NestedInclude1.NestedInclude2 +Module type `NestedInclude1.NestedInclude2` diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md index f041aa93d1..470d378376 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md @@ -2,7 +2,7 @@ Ocamlary NestedInclude2 -Module type Ocamlary.NestedInclude2 +Module type `Ocamlary.NestedInclude2` diff --git a/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md b/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md index c7295401d4..987a93d37e 100644 --- a/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md +++ b/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md @@ -2,7 +2,7 @@ Ocamlary RECOLLECTION -Module type Ocamlary.RECOLLECTION +Module type `Ocamlary.RECOLLECTION` diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md index 9d23a3cbc9..63a80fd7e6 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleA' -Module InnerModuleA.InnerModuleA' +Module `InnerModuleA.InnerModuleA'` -This comment is for InnerModuleA' . +This comment is for `InnerModuleA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md index 062efc7d2e..8899025c1a 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -4,9 +4,9 @@ RecollectionModule InnerModuleA -Module RecollectionModule.InnerModuleA +Module `RecollectionModule.InnerModuleA` -This comment is for InnerModuleA . +This comment is for `InnerModuleA` . diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index bf291e61c6..668829e097 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -6,9 +6,9 @@ InnerModuleA InnerModuleTypeA' -Module type InnerModuleA.InnerModuleTypeA' +Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for InnerModuleTypeA' . +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md index f8fc3ce567..3832b5e30f 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -2,7 +2,7 @@ Ocamlary RecollectionModule -Module type Ocamlary.RecollectionModule +Module type `Ocamlary.RecollectionModule` diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md index d6fd1ce584..cded91ccb3 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md @@ -4,7 +4,7 @@ SigForMod Inner -Module SigForMod.Inner +Module `SigForMod.Inner` diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md index e80f1e82d6..93be426168 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md @@ -6,4 +6,4 @@ Inner Empty -Module type Inner.Empty \ No newline at end of file +Module type `Inner.Empty` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.md index f585bb4669..1a640ea449 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.md @@ -2,7 +2,7 @@ Ocamlary SigForMod -Module type Ocamlary.SigForMod +Module type `Ocamlary.SigForMod` There's a signature in a module in this signature. diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.md index 765d2ee678..49e588cc9e 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md @@ -2,7 +2,7 @@ Ocamlary SuperSig -Module type Ocamlary.SuperSig +Module type `Ocamlary.SuperSig` diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md index eeec955a78..700b55312b 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md @@ -4,7 +4,7 @@ SuperSig EmptySig -Module type SuperSig.EmptySig +Module type `SuperSig.EmptySig` diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md index cd54601f98..ae32c4cb7d 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md @@ -4,7 +4,7 @@ SuperSig One -Module type SuperSig.One +Module type `SuperSig.One` diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md index a9b585d699..8ff46b3b5d 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md @@ -6,7 +6,7 @@ SubSigA SubSigAMod -Module SubSigA.SubSigAMod +Module `SubSigA.SubSigAMod` diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md index bacf3a486d..0221d59751 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -4,7 +4,7 @@ SuperSig SubSigA -Module type SuperSig.SubSigA +Module type `SuperSig.SubSigA` ### A Labeled Section Header Inside of a Signature diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md index ddbfb701df..23db89975a 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md @@ -4,7 +4,7 @@ SuperSig SubSigB -Module type SuperSig.SubSigB +Module type `SuperSig.SubSigB` ### Another Labeled Section Header Inside of a Signature diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md index c4692c37c0..50be165fdc 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md @@ -4,4 +4,4 @@ SuperSig SuperSig -Module type SuperSig.SuperSig \ No newline at end of file +Module type `SuperSig.SuperSig` \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md index 9c3266344e..26d038618d 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md @@ -4,7 +4,7 @@ ToInclude IncludedA -Module ToInclude.IncludedA +Module `ToInclude.IncludedA` diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.md index a5d59c8810..6a54a48715 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md @@ -2,7 +2,7 @@ Ocamlary ToInclude -Module type Ocamlary.ToInclude +Module type `Ocamlary.ToInclude` diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md index c7fd74d8a7..2a6af20caa 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md @@ -4,7 +4,7 @@ ToInclude IncludedB -Module type ToInclude.IncludedB +Module type `ToInclude.IncludedB` diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExt.md b/test/generators/markdown/Ocamlary.module-type-TypeExt.md index 94bc50d5b9..22cfaaa6cb 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExt.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExt.md @@ -2,7 +2,7 @@ Ocamlary TypeExt -Module type Ocamlary.TypeExt +Module type `Ocamlary.TypeExt` diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md index afa348df42..82cead7046 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md @@ -2,7 +2,7 @@ Ocamlary TypeExtPruned -Module type Ocamlary.TypeExtPruned +Module type `Ocamlary.TypeExtPruned` diff --git a/test/generators/markdown/Ocamlary.module-type-With1.M.md b/test/generators/markdown/Ocamlary.module-type-With1.M.md index 08934da2e8..431870afcf 100644 --- a/test/generators/markdown/Ocamlary.module-type-With1.M.md +++ b/test/generators/markdown/Ocamlary.module-type-With1.M.md @@ -4,7 +4,7 @@ With1 M -Module With1.M +Module `With1.M` diff --git a/test/generators/markdown/Ocamlary.module-type-With1.md b/test/generators/markdown/Ocamlary.module-type-With1.md index d69bf3a95f..e9c27d3bad 100644 --- a/test/generators/markdown/Ocamlary.module-type-With1.md +++ b/test/generators/markdown/Ocamlary.module-type-With1.md @@ -2,7 +2,7 @@ Ocamlary With1 -Module type Ocamlary.With1 +Module type `Ocamlary.With1` diff --git a/test/generators/markdown/Ocamlary.module-type-With11.N.md b/test/generators/markdown/Ocamlary.module-type-With11.N.md index 69989d4ff9..56d197d763 100644 --- a/test/generators/markdown/Ocamlary.module-type-With11.N.md +++ b/test/generators/markdown/Ocamlary.module-type-With11.N.md @@ -4,7 +4,7 @@ With11 N -Module With11.N +Module `With11.N` diff --git a/test/generators/markdown/Ocamlary.module-type-With11.md b/test/generators/markdown/Ocamlary.module-type-With11.md index 788a44e30e..2067d152bd 100644 --- a/test/generators/markdown/Ocamlary.module-type-With11.md +++ b/test/generators/markdown/Ocamlary.module-type-With11.md @@ -2,7 +2,7 @@ Ocamlary With11 -Module type Ocamlary.With11 +Module type `Ocamlary.With11` diff --git a/test/generators/markdown/Ocamlary.module-type-With8.M.N.md b/test/generators/markdown/Ocamlary.module-type-With8.M.N.md index 719b256b25..f324d9c3b0 100644 --- a/test/generators/markdown/Ocamlary.module-type-With8.M.N.md +++ b/test/generators/markdown/Ocamlary.module-type-With8.M.N.md @@ -6,7 +6,7 @@ M N -Module M.N +Module `M.N` diff --git a/test/generators/markdown/Ocamlary.module-type-With8.M.md b/test/generators/markdown/Ocamlary.module-type-With8.M.md index 43d67f6a96..aee10b7480 100644 --- a/test/generators/markdown/Ocamlary.module-type-With8.M.md +++ b/test/generators/markdown/Ocamlary.module-type-With8.M.md @@ -4,7 +4,7 @@ With8 M -Module With8.M +Module `With8.M` diff --git a/test/generators/markdown/Ocamlary.module-type-With8.md b/test/generators/markdown/Ocamlary.module-type-With8.md index c127b51a56..6a1a856d27 100644 --- a/test/generators/markdown/Ocamlary.module-type-With8.md +++ b/test/generators/markdown/Ocamlary.module-type-With8.md @@ -2,7 +2,7 @@ Ocamlary With8 -Module type Ocamlary.With8 +Module type `Ocamlary.With8` diff --git a/test/generators/markdown/Ocamlary.one_method_class.md b/test/generators/markdown/Ocamlary.one_method_class.md index ed0a7a2b02..a398dd13bd 100644 --- a/test/generators/markdown/Ocamlary.one_method_class.md +++ b/test/generators/markdown/Ocamlary.one_method_class.md @@ -2,7 +2,7 @@ Ocamlary one_method_class -Class Ocamlary.one_method_class +Class `Ocamlary.one_method_class` diff --git a/test/generators/markdown/Ocamlary.param_class.md b/test/generators/markdown/Ocamlary.param_class.md index c628e846e2..2a6db27d60 100644 --- a/test/generators/markdown/Ocamlary.param_class.md +++ b/test/generators/markdown/Ocamlary.param_class.md @@ -2,7 +2,7 @@ Ocamlary param_class -Class Ocamlary.param_class +Class `Ocamlary.param_class` diff --git a/test/generators/markdown/Ocamlary.two_method_class.md b/test/generators/markdown/Ocamlary.two_method_class.md index 95d7ca1870..4415b4ce64 100644 --- a/test/generators/markdown/Ocamlary.two_method_class.md +++ b/test/generators/markdown/Ocamlary.two_method_class.md @@ -2,7 +2,7 @@ Ocamlary two_method_class -Class Ocamlary.two_method_class +Class `Ocamlary.two_method_class` diff --git a/test/generators/markdown/Recent.X.md b/test/generators/markdown/Recent.X.md index 43e5518a91..485087eb11 100644 --- a/test/generators/markdown/Recent.X.md +++ b/test/generators/markdown/Recent.X.md @@ -2,7 +2,7 @@ Recent X -Module Recent.X +Module `Recent.X` diff --git a/test/generators/markdown/Recent.Z.Y.X.md b/test/generators/markdown/Recent.Z.Y.X.md index 78ce61b1f3..4456904204 100644 --- a/test/generators/markdown/Recent.Z.Y.X.md +++ b/test/generators/markdown/Recent.Z.Y.X.md @@ -6,7 +6,7 @@ Y X -Module Y.X +Module `Y.X` diff --git a/test/generators/markdown/Recent.Z.Y.md b/test/generators/markdown/Recent.Z.Y.md index ae087a1db9..734c1fe9f4 100644 --- a/test/generators/markdown/Recent.Z.Y.md +++ b/test/generators/markdown/Recent.Z.Y.md @@ -4,7 +4,7 @@ Z Y -Module Z.Y +Module `Z.Y` diff --git a/test/generators/markdown/Recent.Z.md b/test/generators/markdown/Recent.Z.md index ce353f8c63..8e62fae644 100644 --- a/test/generators/markdown/Recent.Z.md +++ b/test/generators/markdown/Recent.Z.md @@ -2,7 +2,7 @@ Recent Z -Module Recent.Z +Module `Recent.Z` diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index ab98cd4790..599c7ee7ba 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -1,6 +1,6 @@ Recent -Module Recent +Module `Recent` @@ -40,7 +40,7 @@ foo -######    a : int ; +######    `;int : a` } @@ -64,7 +64,7 @@ foo -######    a : int ; +######    `;int : a` } -> unit [gadt](#type-gadt) @@ -74,21 +74,21 @@ foo -######    | `A +######    `| ` `` `A `` -######    | `B of int +######    `| ` `` int of `B `` -######    | `C +######    `| ` `` `C `` foo -######    | `D +######    `| ` `` `D `` bar diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index 482faba3c0..5dbddabf36 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -2,7 +2,7 @@ Recent PolyS -Module type Recent.PolyS +Module type `Recent.PolyS` @@ -10,10 +10,10 @@ Module type Recent.PolyS -######    | `A +######    `| ` `` `A `` -######    | `B +######    `| ` `` `B `` ] \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-S.md b/test/generators/markdown/Recent.module-type-S.md index b5379a4ec4..f55f8316ff 100644 --- a/test/generators/markdown/Recent.module-type-S.md +++ b/test/generators/markdown/Recent.module-type-S.md @@ -2,4 +2,4 @@ Recent S -Module type Recent.S \ No newline at end of file +Module type `Recent.S` \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-S1.argument-1-_.md b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md index a976212b40..4032dc6a57 100644 --- a/test/generators/markdown/Recent.module-type-S1.argument-1-_.md +++ b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md @@ -4,4 +4,4 @@ S1 1-_ -Parameter S1.1-_ \ No newline at end of file +Parameter `S1.1-_` \ No newline at end of file diff --git a/test/generators/markdown/Recent.module-type-S1.md b/test/generators/markdown/Recent.module-type-S1.md index 02edd128d5..700ddc2ba2 100644 --- a/test/generators/markdown/Recent.module-type-S1.md +++ b/test/generators/markdown/Recent.module-type-S1.md @@ -2,7 +2,7 @@ Recent S1 -Module type Recent.S1 +Module type `Recent.S1` # Parameters diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md index 86d7107480..73ffed0090 100644 --- a/test/generators/markdown/Recent_impl.B.md +++ b/test/generators/markdown/Recent_impl.B.md @@ -2,7 +2,7 @@ Recent_impl B -Module Recent_impl.B +Module `Recent_impl.B` diff --git a/test/generators/markdown/Recent_impl.Foo.A.md b/test/generators/markdown/Recent_impl.Foo.A.md index 23f1a90837..a6e8d80b62 100644 --- a/test/generators/markdown/Recent_impl.Foo.A.md +++ b/test/generators/markdown/Recent_impl.Foo.A.md @@ -4,7 +4,7 @@ Foo A -Module Foo.A +Module `Foo.A` diff --git a/test/generators/markdown/Recent_impl.Foo.B.md b/test/generators/markdown/Recent_impl.Foo.B.md index 3dd136dc0a..74d5eaecc8 100644 --- a/test/generators/markdown/Recent_impl.Foo.B.md +++ b/test/generators/markdown/Recent_impl.Foo.B.md @@ -4,7 +4,7 @@ Foo B -Module Foo.B +Module `Foo.B` diff --git a/test/generators/markdown/Recent_impl.Foo.md b/test/generators/markdown/Recent_impl.Foo.md index 3d7864dd60..54872db5a2 100644 --- a/test/generators/markdown/Recent_impl.Foo.md +++ b/test/generators/markdown/Recent_impl.Foo.md @@ -2,7 +2,7 @@ Recent_impl Foo -Module Recent_impl.Foo +Module `Recent_impl.Foo` diff --git a/test/generators/markdown/Recent_impl.md b/test/generators/markdown/Recent_impl.md index 9587407c22..6e18d42fa6 100644 --- a/test/generators/markdown/Recent_impl.md +++ b/test/generators/markdown/Recent_impl.md @@ -1,6 +1,6 @@ Recent_impl -Module Recent_impl +Module `Recent_impl` diff --git a/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md b/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md index 1bcfc3532b..85817bf2b3 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md +++ b/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md @@ -6,4 +6,4 @@ F 1-_ -Parameter F.1-_ \ No newline at end of file +Parameter `F.1-_` \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.module-type-S.F.md b/test/generators/markdown/Recent_impl.module-type-S.F.md index 3a6fcc4fe1..35c05c2c2b 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.F.md +++ b/test/generators/markdown/Recent_impl.module-type-S.F.md @@ -4,7 +4,7 @@ S F -Module S.F +Module `S.F` # Parameters diff --git a/test/generators/markdown/Recent_impl.module-type-S.X.md b/test/generators/markdown/Recent_impl.module-type-S.X.md index ad1aa0bf60..cbbae12c02 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.X.md +++ b/test/generators/markdown/Recent_impl.module-type-S.X.md @@ -4,4 +4,4 @@ S X -Module S.X \ No newline at end of file +Module `S.X` \ No newline at end of file diff --git a/test/generators/markdown/Recent_impl.module-type-S.md b/test/generators/markdown/Recent_impl.module-type-S.md index 45a3fc82c0..33750a376d 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.md +++ b/test/generators/markdown/Recent_impl.module-type-S.md @@ -2,7 +2,7 @@ Recent_impl S -Module type Recent_impl.S +Module type `Recent_impl.S` diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index 7d1da64559..3a9e10295e 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -1,6 +1,6 @@ Section -Module Section +Module `Section` This is the module comment. Eventually, sections won't be allowed in it. @@ -31,6 +31,6 @@ Foo bar. --- -# _This_ section **title** has markup +# _This_ `section` **title** has markup But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. \ No newline at end of file diff --git a/test/generators/markdown/Stop.N.md b/test/generators/markdown/Stop.N.md index 4c3a4846f8..ae8899e250 100644 --- a/test/generators/markdown/Stop.N.md +++ b/test/generators/markdown/Stop.N.md @@ -2,7 +2,7 @@ Stop N -Module Stop.N +Module `Stop.N` diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md index 5cc6980553..517e085c83 100644 --- a/test/generators/markdown/Stop.md +++ b/test/generators/markdown/Stop.md @@ -1,6 +1,6 @@ Stop -Module Stop +Module `Stop` This test cases exercises stop comments. @@ -13,7 +13,7 @@ This test cases exercises stop comments. This is normal commented text. -The next value is bar , and it should be missing from the documentation. There is also an entire module, M , which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. +The next value is `bar` , and it should be missing from the documentation. There is also an entire module, `M` , which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. Documentation is on again. diff --git a/test/generators/markdown/Stop_dead_link_doc.Foo.md b/test/generators/markdown/Stop_dead_link_doc.Foo.md index c9f285b2b2..69df6db5cc 100644 --- a/test/generators/markdown/Stop_dead_link_doc.Foo.md +++ b/test/generators/markdown/Stop_dead_link_doc.Foo.md @@ -2,7 +2,7 @@ Stop_dead_link_doc Foo -Module Stop_dead_link_doc.Foo +Module `Stop_dead_link_doc.Foo` diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index f466ad47a9..e6c7b6b455 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -1,6 +1,6 @@ Stop_dead_link_doc -Module Stop_dead_link_doc +Module `Stop_dead_link_doc` diff --git a/test/generators/markdown/Toplevel_comments.Alias.md b/test/generators/markdown/Toplevel_comments.Alias.md index 65bdfdd6c2..07fcf6e532 100644 --- a/test/generators/markdown/Toplevel_comments.Alias.md +++ b/test/generators/markdown/Toplevel_comments.Alias.md @@ -2,11 +2,11 @@ Toplevel_comments Alias -Module Toplevel_comments.Alias +Module `Toplevel_comments.Alias` -Doc of Alias . +Doc of `Alias` . -Doc of T , part 2. +Doc of `T` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md index ca771f9b42..d836877fb2 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md @@ -4,7 +4,7 @@ Comments_on_open M -Module Comments_on_open.M +Module `Comments_on_open.M` diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md index 6c4d450449..3a8bd528e6 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -2,7 +2,7 @@ Toplevel_comments Comments_on_open -Module Toplevel_comments.Comments_on_open +Module `Toplevel_comments.Comments_on_open` @@ -12,4 +12,4 @@ Module Toplevel_comments.Comments_on_open --- -Comments attached to open are treated as floating comments. Referencing [Section](#sec) [M.t](Toplevel_comments.Comments_on_open.M.md#type-t) works \ No newline at end of file +Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Include_inline'.md b/test/generators/markdown/Toplevel_comments.Include_inline'.md index bf834649e9..4a4e522121 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline'.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline'.md @@ -2,11 +2,11 @@ Toplevel_comments Include_inline' -Module Toplevel_comments.Include_inline' +Module `Toplevel_comments.Include_inline'` -Doc of Include_inline , part 1. +Doc of `Include_inline` , part 1. -Doc of Include_inline , part 2. +Doc of `Include_inline` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.Include_inline.md b/test/generators/markdown/Toplevel_comments.Include_inline.md index 8022368f62..12cfed60ee 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline.md @@ -2,9 +2,9 @@ Toplevel_comments Include_inline -Module Toplevel_comments.Include_inline +Module `Toplevel_comments.Include_inline` -Doc of T , part 2. +Doc of `T` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.M''.md b/test/generators/markdown/Toplevel_comments.M''.md index f9071f503f..9b97d858d2 100644 --- a/test/generators/markdown/Toplevel_comments.M''.md +++ b/test/generators/markdown/Toplevel_comments.M''.md @@ -2,8 +2,8 @@ Toplevel_comments M'' -Module Toplevel_comments.M'' +Module `Toplevel_comments.M''` -Doc of M'' , part 1. +Doc of `M''` , part 1. -Doc of M'' , part 2. \ No newline at end of file +Doc of `M''` , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.M'.md b/test/generators/markdown/Toplevel_comments.M'.md index 2bb36648a1..5a5003a083 100644 --- a/test/generators/markdown/Toplevel_comments.M'.md +++ b/test/generators/markdown/Toplevel_comments.M'.md @@ -2,6 +2,6 @@ Toplevel_comments M' -Module Toplevel_comments.M' +Module `Toplevel_comments.M'` -Doc of M' from outside \ No newline at end of file +Doc of `M'` from outside \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.M.md b/test/generators/markdown/Toplevel_comments.M.md index c8f121c8cd..c8701628e1 100644 --- a/test/generators/markdown/Toplevel_comments.M.md +++ b/test/generators/markdown/Toplevel_comments.M.md @@ -2,6 +2,6 @@ Toplevel_comments M -Module Toplevel_comments.M +Module `Toplevel_comments.M` -Doc of M \ No newline at end of file +Doc of `M` \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md index 9ff17ab301..2fd084c307 100644 --- a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -2,9 +2,9 @@ Toplevel_comments Ref_in_synopsis -Module Toplevel_comments.Ref_in_synopsis +Module `Toplevel_comments.Ref_in_synopsis` -[t](#type-t) . +[`t`](#type-t) . This reference should resolve in the context of this module, even when used as a synopsis. diff --git a/test/generators/markdown/Toplevel_comments.c1.md b/test/generators/markdown/Toplevel_comments.c1.md index 3b1e120bf1..37bd69b324 100644 --- a/test/generators/markdown/Toplevel_comments.c1.md +++ b/test/generators/markdown/Toplevel_comments.c1.md @@ -2,8 +2,8 @@ Toplevel_comments c1 -Class Toplevel_comments.c1 +Class `Toplevel_comments.c1` -Doc of c1 , part 1. +Doc of `c1` , part 1. -Doc of c1 , part 2. \ No newline at end of file +Doc of `c1` , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.c2.md b/test/generators/markdown/Toplevel_comments.c2.md index dccbd59122..56ebb35850 100644 --- a/test/generators/markdown/Toplevel_comments.c2.md +++ b/test/generators/markdown/Toplevel_comments.c2.md @@ -2,8 +2,8 @@ Toplevel_comments c2 -Class Toplevel_comments.c2 +Class `Toplevel_comments.c2` -Doc of c2 . +Doc of `c2` . -Doc of ct , part 2. \ No newline at end of file +Doc of `ct` , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.class-type-ct.md b/test/generators/markdown/Toplevel_comments.class-type-ct.md index 62eaf06f50..851f09edf5 100644 --- a/test/generators/markdown/Toplevel_comments.class-type-ct.md +++ b/test/generators/markdown/Toplevel_comments.class-type-ct.md @@ -2,8 +2,8 @@ Toplevel_comments ct -Class type Toplevel_comments.ct +Class type `Toplevel_comments.ct` -Doc of ct , part 1. +Doc of `ct` , part 1. -Doc of ct , part 2. \ No newline at end of file +Doc of `ct` , part 2. \ No newline at end of file diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index 07f5940cf0..b6ab001d4b 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -1,6 +1,6 @@ Toplevel_comments -Module Toplevel_comments +Module `Toplevel_comments` A doc comment at the beginning of a module is considered to be that module's doc. diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md index d9418541c8..0654cc3620 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md @@ -2,11 +2,11 @@ Toplevel_comments Include_inline_T' -Module type Toplevel_comments.Include_inline_T' +Module type `Toplevel_comments.Include_inline_T'` -Doc of Include_inline_T' , part 1. +Doc of `Include_inline_T'` , part 1. -Doc of Include_inline_T' , part 2. +Doc of `Include_inline_T'` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md index 588ad6e418..f7b06b85f9 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md @@ -2,9 +2,9 @@ Toplevel_comments Include_inline_T -Module type Toplevel_comments.Include_inline_T +Module type `Toplevel_comments.Include_inline_T` -Doc of T , part 2. +Doc of `T` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.module-type-T.md b/test/generators/markdown/Toplevel_comments.module-type-T.md index a0590073a6..1b9f00fded 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-T.md +++ b/test/generators/markdown/Toplevel_comments.module-type-T.md @@ -2,11 +2,11 @@ Toplevel_comments T -Module type Toplevel_comments.T +Module type `Toplevel_comments.T` -Doc of T , part 1. +Doc of `T` , part 1. -Doc of T , part 2. +Doc of `T` , part 2. diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 2be8a7a05d..4c95dfb6d2 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -1,6 +1,6 @@ Type -Module Type +Module `Type` @@ -112,7 +112,7 @@ Some -######    a : int ; +######    `;int : a` } @@ -150,7 +150,7 @@ foo -######    a : int ; +######    `;int : a` } @@ -192,27 +192,27 @@ foo -######    a : int ; +######    `;int : a` -######    mutable b : int ; +######    `;int : b mutable` -######    c : int ; +######    `;int : c` foo -######    d : int ; +######    `;int : d` -######    e : 'a. 'a ; +######    `;'a'a. : e` } @@ -222,19 +222,19 @@ foo -######    | `A +######    `| ` `` `A `` -######    | `B of int +######    `| ` `` int of `B `` -######    | `C of int * unit +######    `| ` `` unit* int of `C `` -######    | `D +######    `| ` `` `D `` ] @@ -244,11 +244,11 @@ foo -######    | [polymorphic_variant](#type-polymorphic_variant) +######    `| ` [polymorphic_variant](#type-polymorphic_variant) -######    | `E +######    `| ` `` `E `` ] @@ -258,7 +258,7 @@ foo -######    | `A of [ `B | `C ] +######    `| ` `` [ `B | `C ] of `A `` ] @@ -272,7 +272,7 @@ foo -######    | [polymorphic_variant](#type-polymorphic_variant) +######    `| ` [polymorphic_variant](#type-polymorphic_variant) ] diff --git a/test/generators/markdown/Type.module-type-X.md b/test/generators/markdown/Type.module-type-X.md index 517c602e08..8b685f4bea 100644 --- a/test/generators/markdown/Type.module-type-X.md +++ b/test/generators/markdown/Type.module-type-X.md @@ -2,7 +2,7 @@ Type X -Module type Type.X +Module type `Type.X` diff --git a/test/generators/markdown/Val.md b/test/generators/markdown/Val.md index ea6fc17163..028900f886 100644 --- a/test/generators/markdown/Val.md +++ b/test/generators/markdown/Val.md @@ -1,6 +1,6 @@ Val -Module Val +Module `Val` diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index 0f9e26567b..6e0395559b 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -4,7 +4,7 @@ mld --- -This is an .mld file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. +This is an `.mld` file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. It will have a TOC generated from section headings. From c4922c8ca153a502af62bea3906b38122f6fb5b3 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Thu, 3 Feb 2022 21:01:29 +0100 Subject: [PATCH 24/38] Fix printing of documentation comments --- src/markdown/generator.ml | 42 +------- test/generators/markdown/Bugs.md | 2 +- test/generators/markdown/External.md | 2 +- test/generators/markdown/Include2.md | 2 +- test/generators/markdown/Markup.md | 2 +- test/generators/markdown/Module.md | 2 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 2 +- .../Ocamlary.CollectionModule.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../markdown/Ocamlary.CollectionModule.md | 6 +- ...1-Collection.InnerModuleA.InnerModuleA'.md | 2 +- ...peOf.argument-1-Collection.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- ...ary.FunctorTypeOf.argument-1-Collection.md | 6 +- .../markdown/Ocamlary.FunctorTypeOf.md | 2 +- ...Recollection.InnerModuleA.InnerModuleA'.md | 2 +- .../Ocamlary.Recollection.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- ...argument-1-C.InnerModuleA.InnerModuleA'.md | 2 +- ....Recollection.argument-1-C.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../Ocamlary.Recollection.argument-1-C.md | 6 +- .../markdown/Ocamlary.Recollection.md | 6 +- test/generators/markdown/Ocamlary.With10.md | 1 + test/generators/markdown/Ocamlary.md | 98 ++++++++++++------- ...ule-type-A.Q.InnerModuleA.InnerModuleA'.md | 2 +- .../Ocamlary.module-type-A.Q.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../markdown/Ocamlary.module-type-A.Q.md | 6 +- ...ule-type-B.Q.InnerModuleA.InnerModuleA'.md | 2 +- .../Ocamlary.module-type-B.Q.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../markdown/Ocamlary.module-type-B.Q.md | 6 +- ...ule-type-C.Q.InnerModuleA.InnerModuleA'.md | 2 +- .../Ocamlary.module-type-C.Q.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../markdown/Ocamlary.module-type-C.Q.md | 6 +- ...e-COLLECTION.InnerModuleA.InnerModuleA'.md | 2 +- ...ary.module-type-COLLECTION.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../Ocamlary.module-type-COLLECTION.md | 6 +- ...e-type-MMM.C.InnerModuleA.InnerModuleA'.md | 2 +- ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- .../markdown/Ocamlary.module-type-MMM.C.md | 6 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 2 +- ...le-type-RecollectionModule.InnerModuleA.md | 6 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 2 +- ...Ocamlary.module-type-RecollectionModule.md | 4 +- test/generators/markdown/Recent.md | 2 +- test/generators/markdown/Toplevel_comments.md | 24 ++--- test/generators/markdown/Type.md | 10 +- 52 files changed, 167 insertions(+), 180 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 8162bc31ab..980a40d247 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -141,33 +141,6 @@ and description_one args { Description.key; definition; _ } = in paragraph (join (text "@") (join key (text ":")) ++ def) -let rec acc_text (l : Block.t) : string = - match l with - | [] -> "" - | h :: rest -> ( - match h.desc with Paragraph i -> inline_text i ^ acc_text rest | _ -> "") - -and inline_text (i : Inline.t) = - let code_span s = - if String.contains s '`' then "`` " ^ s ^ "``" else "`" ^ s ^ "`" - in - match i with - | [] -> "" - | h :: rest -> ( - match h.desc with - | Text s -> s ^ inline_text rest - | Source s -> - let rec source_text (s' : Source.t) = - match s' with - | [] -> "" - | t :: rest_t -> ( - match t with - | Elt i -> inline_text i ^ source_text rest_t - | _ -> "") - in - code_span (source_text s) - | _ -> "") - (** Generates the 6-heading used to differentiate items. Non-breaking spaces are inserted just before the text, to simulate indentation depending on [nesting_level]. @@ -217,11 +190,6 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = | _ -> Stop_and_keep) in let f (content, doc, (anchor : Odoc_document.Url.t option)) = - let doc = - match doc with - | [] -> noop_block - | doc -> paragraph (text (acc_text doc)) - in let content = let nesting_level = nesting_level + 1 in match content with @@ -233,7 +201,7 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = (item_heading nesting_level (source_code c args)) (continue rest) in - let item = blocks content doc in + let item = blocks content (block args doc) in if args.generate_links then let anchor = match anchor with Some a -> a.anchor | None -> "" @@ -290,11 +258,7 @@ and item (l : Item.t list) args nesting_level = | begin_code, content -> (begin_code, content) in let render_declaration ~anchor ~doc heading content = - let doc = - match doc with - | [] -> noop_block - | doc -> paragraph (text (acc_text doc)) - and anchor = + let anchor = if args.generate_links then let anchor = match anchor with Some x -> x.Url.Anchor.anchor | None -> "" @@ -304,7 +268,7 @@ and item (l : Item.t list) args nesting_level = in anchor +++ item_heading nesting_level (source_code heading args) - +++ content +++ doc +++ continue rest + +++ content +++ block args doc +++ continue rest in match take_code_from_declaration content with | code, [] -> diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index 748d121f26..637d9d8cbd 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -16,4 +16,4 @@ Module `Bugs` > ? bar : 'a -> unit -> unit -Triggers an assertion failure when \ No newline at end of file +Triggers an assertion failure when [https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) is not fixed. \ No newline at end of file diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md index 09df98011f..c03ff524e6 100644 --- a/test/generators/markdown/External.md +++ b/test/generators/markdown/External.md @@ -9,4 +9,4 @@ Module `External` > unit -> unit -Foo \ No newline at end of file +Foo _bar_ . \ No newline at end of file diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index b3a360f8d4..0d7f501d4d 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -27,7 +27,7 @@ Top-comment of Y. ###### module [Y_include_synopsis](Include2.Y_include_synopsis.md) -The `include Y` +The `include Y` below should have the synopsis from `Y` 's top-comment attached to it. diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index cd25993b91..9bf7f46367 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -172,7 +172,7 @@ Each comment can end with zero or more tags. Here are some examples: > unit -Comments in structure items +Comments in structure items **support** _markup_ , t o o . Some modules to support references. diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index 3a8d537759..43248bd356 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -11,7 +11,7 @@ Foo. > unit -The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See +The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See [https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701) . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md index 3c601438e3..875f6f6728 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index a29e12793e..6405679355 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -15,16 +15,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.CollectionModule.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index ff0c7b4494..9ed0055792 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md index 513df6db4d..0355a783a5 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.md @@ -10,7 +10,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -20,7 +20,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.CollectionModule.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -29,4 +29,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md index 286f7ab1e2..316e22ab77 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md index fdbd083364..9be53e43d9 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -17,16 +17,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md index d293d0dbc5..2e8df6dbae 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md index a2478c400e..8972e2f817 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md index d44365e14f..92c93cb63e 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md @@ -21,4 +21,4 @@ This comment is for `FunctorTypeOf` . > [Collection.collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md index 4ee0d4f694..debd9211e9 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index 7783aa0cf6..339dcbb6e8 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -15,16 +15,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.Recollection.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md index dc61ff7732..7dd25e3085 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md index 3587e5e3cf..74bc89361a 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md index 775ecd56ed..0e67e634fb 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -17,16 +17,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.Recollection.argument-1-C.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md index f66011c775..93055cef64 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md index 5d64ca4381..543258b17a 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md index 0d4663606c..a2c77f97b1 100644 --- a/test/generators/markdown/Ocamlary.Recollection.md +++ b/test/generators/markdown/Ocamlary.Recollection.md @@ -21,7 +21,7 @@ This comment is for `CollectionModule` . > [C.element](Ocamlary.Recollection.argument-1-C.md#type-element) list -This comment is for `collection` +This comment is for `collection` . @@ -34,7 +34,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.Recollection.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -43,4 +43,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.With10.md b/test/generators/markdown/Ocamlary.With10.md index 532c4567fb..1f89876e0a 100644 --- a/test/generators/markdown/Ocamlary.With10.md +++ b/test/generators/markdown/Ocamlary.With10.md @@ -8,3 +8,4 @@ Module `Ocamlary.With10` ###### module type [T](Ocamlary.With10.module-type-T.md) +[`With10.T`](Ocamlary.With10.module-type-T.md) is a submodule type. \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index b6cd3cb5e6..6863345df7 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -140,7 +140,7 @@ A plain, empty module signature alias of ###### module [ModuleWithSignature](Ocamlary.ModuleWithSignature.md) -A plain module of a signature of +A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) @@ -168,7 +168,7 @@ For a good time, see [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSig ###### module [Buffer](Ocamlary.Buffer.md) -References are resolved after everything, so `{!Buffer.t}` +References are resolved after everything, so `{!Buffer.t}` won't resolve. Some text before exception title. @@ -200,13 +200,13 @@ Unary exception constructor over binary tuple ###### exception EmptySig - +[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and [`EmptySig`](#exception-EmptySig) is this exception. ###### exception EmptySigAlias - +[`EmptySigAlias`](#exception-EmptySigAlias) is this exception. ### Basic type and value stuff with advanced doc comments @@ -219,7 +219,7 @@ Unary exception constructor over binary tuple > 'a -> 'b - +[`a_function`](#type-a_function) is this type and [`a_function`](#val-a_function) is the value below. @@ -228,7 +228,11 @@ Unary exception constructor over binary tuple > x : int -> int -This is `a_function` +This is `a_function` with param and return type. + +@parameter x: + +@returns: @@ -251,7 +255,7 @@ This is `a_function` > unit -> unit - +@raises Not_found: @@ -260,7 +264,7 @@ This is `a_function` > string - +@see [http://ocaml.org/](http://ocaml.org/): @@ -269,7 +273,7 @@ This is `a_function` > string - +@see `some_file`: @@ -278,7 +282,7 @@ This is `a_function` > string - +@see some_doc: @@ -289,6 +293,8 @@ This is `a_function` This value was introduced in the Mesozoic era. +@since: mesozoic + ###### val changing : @@ -298,6 +304,12 @@ This value was introduced in the Mesozoic era. This value has had changes in 1.0.0, 1.1.0, and 1.2.0. +@before 1.0.0: + +@before 1.1.0: + +@version: 1.2.0 + ### Some Operators --- @@ -408,7 +420,7 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. ###### module [CollectionModule](Ocamlary.CollectionModule.md) -This comment is for `CollectionModule` +This comment is for `CollectionModule` . @@ -450,13 +462,13 @@ This module type includes two signatures. ###### module [FunctorTypeOf](Ocamlary.FunctorTypeOf.md) -This comment is for `FunctorTypeOf` +This comment is for `FunctorTypeOf` . ###### module type [IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) -This comment is for `IncludeModuleType` +This comment is for `IncludeModuleType` . @@ -482,17 +494,19 @@ This comment is for `IncludeModuleType` ######    `;int : field1` -This comment is for `field1` +This comment is for `field1` . ######    `;int : field2` -This comment is for `field2` +This comment is for `field2` . } -This comment is for `record`This comment is also for `record` +This comment is for `record` . + +This comment is also for `record` . @@ -502,19 +516,19 @@ This comment is for `record`This comment is also for `record` ######    `;int : a mutable` -`a` +`a` is first and mutable ######    `;unit : b` -`b` +`b` is second and immutable ######    `;int : c mutable` -`c` +`c` is third and mutable } @@ -536,27 +550,29 @@ This comment is for `record`This comment is also for `record` ######    | TagA -This comment is for `TagA` +This comment is for `TagA` . ######    | ConstrB of int -This comment is for `ConstrB` +This comment is for `ConstrB` . ######    | ConstrC of int * int -This comment is for binary `ConstrC` +This comment is for binary `ConstrC` . ######    | ConstrD of int * int -This comment is for unary `ConstrD` +This comment is for unary `ConstrD` of binary tuple. -This comment is for `variant`This comment is also for `variant` +This comment is for `variant` . + +This comment is also for `variant` . @@ -572,7 +588,9 @@ This comment is for `variant`This comment is also for `variant` ] -This comment is for `poly_variant`Wow! It was a polymorphic variant! +This comment is for `poly_variant` . + +Wow! It was a polymorphic variant! @@ -594,7 +612,9 @@ This comment is for `poly_variant`Wow! It was a polymorphic variant! ######    | Exist : 'a * 'b -> ( 'b , unit ) [full_gadt](#type-full_gadt) -This comment is for `full_gadt`Wow! It was a GADT! +This comment is for `full_gadt` . + +Wow! It was a GADT! @@ -612,7 +632,9 @@ This comment is for `full_gadt`Wow! It was a GADT! ######    | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt](#type-partial_gadt) -This comment is for `partial_gadt`Wow! It was a mixed GADT! +This comment is for `partial_gadt` . + +Wow! It was a mixed GADT! @@ -621,7 +643,7 @@ This comment is for `partial_gadt`Wow! It was a mixed GADT! > [variant](#type-variant) -This comment is for `alias` +This comment is for `alias` . @@ -630,7 +652,7 @@ This comment is for `alias` > ( [alias](#type-alias) * [alias](#type-alias) ) * [alias](#type-alias) * ( [alias](#type-alias) * [alias](#type-alias) ) -This comment is for `tuple` +This comment is for `tuple` . @@ -652,7 +674,7 @@ This comment is for `tuple` ######    | ConstrD of int * int -This comment is for `variant_alias` +This comment is for `variant_alias` . @@ -668,7 +690,7 @@ This comment is for `variant_alias` } -This comment is for `record_alias` +This comment is for `record_alias` . @@ -684,7 +706,7 @@ This comment is for `record_alias` ] -This comment is for `poly_variant_union` +This comment is for `poly_variant_union` . @@ -801,7 +823,7 @@ This comment is for `poly_variant_union` ######    | Exist : 'a * 'b -> ( 'b , unit ) [full_gadt_alias](#type-full_gadt_alias) -This comment is for `full_gadt_alias` +This comment is for `full_gadt_alias` . @@ -819,7 +841,7 @@ This comment is for `full_gadt_alias` ######    | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt_alias](#type-partial_gadt_alias) -This comment is for `partial_gadt_alias` +This comment is for `partial_gadt_alias` . @@ -828,7 +850,7 @@ This comment is for `partial_gadt_alias` > unit -> exn -This comment is for +This comment is for [`Exn_arrow`](#exception-Exn_arrow) . @@ -842,9 +864,9 @@ This comment is for ######    | B_ish of [mutual_constr_b](#type-mutual_constr_b) -This comment is between +This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and [`mutual_constr_b`](#type-mutual_constr_b) . -This comment is for +This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then [`mutual_constr_b`](#type-mutual_constr_b) . @@ -860,7 +882,7 @@ This comment is for This comment must be here for the next to associate correctly. -This comment is for +This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then [`mutual_constr_a`](#type-mutual_constr_a) . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md index e2517b74df..aa2f1c4aaf 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md index 8eef35af00..c69b0a6c19 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -17,16 +17,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-A.Q.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index d021fdb7de..d352b531ee 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.md b/test/generators/markdown/Ocamlary.module-type-A.Q.md index 447e15f771..5f993f523a 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.module-type-A.Q.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md index 08ebddbcf7..7d5e408943 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md index 7401e10c45..a9df265fb5 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -17,16 +17,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-B.Q.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index aeadf5c54f..4af5552673 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.md b/test/generators/markdown/Ocamlary.module-type-B.Q.md index 3c90e28914..2201312f52 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.module-type-B.Q.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md index d0faa21524..54ed708665 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md index 98009f6ac0..c2e58194bc 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -17,16 +17,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-C.Q.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index fec1083325..7943f99faf 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.md b/test/generators/markdown/Ocamlary.module-type-C.Q.md index 5ff528cc9b..2aa4a78b30 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.module-type-C.Q.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md index 8bc5f3a54f..c242abad8d 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md index 3d886505b3..5f2fa76cec 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -15,16 +15,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-COLLECTION.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md index 27a79c2e34..a3d956ff02 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md index 04245f46a3..d0b05f0b4d 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.module-type-COLLECTION.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md index c6145d6258..d43c606972 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md index 3ec838c10f..e8f4a5f681 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -17,16 +17,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-MMM.C.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md index 8bff26b15f..ba3047c43b 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -19,4 +19,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.md index ee6f469cac..43d7818a2b 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.md @@ -12,7 +12,7 @@ This comment is for `CollectionModule` . ###### type collection -This comment is for `collection` +This comment is for `collection` . @@ -22,7 +22,7 @@ This comment is for `collection` ###### module [InnerModuleA](Ocamlary.module-type-MMM.C.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md index 63a80fd7e6..1c085d575b 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md index 8899025c1a..755c03f1bd 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -15,16 +15,16 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-RecollectionModule.md#type-collection) -This comment is for `t` +This comment is for `t` . ###### module [InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` +This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` \ No newline at end of file +This comment is for `InnerModuleTypeA'` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index 668829e097..6e1f98b7b8 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -17,4 +17,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` \ No newline at end of file +This comment is for `t` . \ No newline at end of file diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md index 3832b5e30f..5a707ceaee 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -22,7 +22,7 @@ Module type `Ocamlary.RecollectionModule` ###### module [InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) -This comment is for `InnerModuleA` +This comment is for `InnerModuleA` . @@ -31,4 +31,4 @@ This comment is for `InnerModuleA` > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` \ No newline at end of file +This comment is for `InnerModuleTypeA` . \ No newline at end of file diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 599c7ee7ba..227e3f7d6e 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -32,7 +32,7 @@ foo ######    | D - +_bar_ diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index b6ab001d4b..aa6f394bea 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -8,31 +8,31 @@ A doc comment at the beginning of a module is considered to be that module's doc ###### module type [T](Toplevel_comments.module-type-T.md) -Doc of `T` +Doc of `T` , part 1. ###### module [Include_inline](Toplevel_comments.Include_inline.md) -Doc of `T` +Doc of `T` , part 2. ###### module [Include_inline'](Toplevel_comments.Include_inline'.md) -Doc of `Include_inline` +Doc of `Include_inline` , part 1. ###### module type [Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) -Doc of `T` +Doc of `T` , part 2. ###### module type [Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) -Doc of `Include_inline_T'` +Doc of `Include_inline_T'` , part 1. @@ -44,43 +44,43 @@ Doc of `M` ###### module [M'](Toplevel_comments.M'.md) -Doc of `M'` +Doc of `M'` from outside ###### module [M''](Toplevel_comments.M''.md) -Doc of `M''` +Doc of `M''` , part 1. ###### module [Alias](Toplevel_comments.Alias.md) -Doc of `Alias` +Doc of `Alias` . ###### class [c1](Toplevel_comments.c1.md) -Doc of `c1` +Doc of `c1` , part 1. ###### class type [ct](Toplevel_comments.class-type-ct.md) -Doc of `ct` +Doc of `ct` , part 1. ###### class [c2](Toplevel_comments.c2.md) -Doc of `c2` +Doc of `c2` . ###### module [Ref_in_synopsis](Toplevel_comments.Ref_in_synopsis.md) - +[`t`](Toplevel_comments.Ref_in_synopsis.md#type-t) . diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 4c95dfb6d2..06a444d3be 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -6,7 +6,7 @@ Module `Type` ###### type abstract -Some +Some _documentation_ . @@ -138,7 +138,7 @@ foo ######    | D - +_bar_ @@ -208,7 +208,7 @@ foo ######    `;int : d` - +_bar_ @@ -423,13 +423,13 @@ foo ######    | Extension -Documentation for +Documentation for [`Extension`](#extension-Extension) . ######    | Another_extension -Documentation for +Documentation for [`Another_extension`](#extension-Another_extension) . From 3c2a8d9ea47d0e0ade5850f76f1491a6741c286d Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Fri, 4 Feb 2022 18:49:48 +0100 Subject: [PATCH 25/38] Fix rendering of nested and documented items --- src/markdown/generator.ml | 64 ++++++++----------- test/generators/markdown/Recent.md | 4 +- .../generators/markdown/Stop_dead_link_doc.md | 2 +- 3 files changed, 31 insertions(+), 39 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 980a40d247..8141c16e96 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -176,45 +176,37 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = else continue rest | Alternative (Expansion { url; expansion; _ }) -> if Link.should_inline url then - documented_src expansion args nesting_level + documented_src expansion args nesting_level +++ continue rest else continue rest - | Subpage p -> - blocks (subpage p.content args (nesting_level + 1)) (continue rest) - | Documented _ | Nested _ -> - let lines, _, rest = - Take.until l ~classify:(function - | DocumentedSrc.Documented { code; doc; anchor; _ } -> - Accum [ (`D code, doc, anchor) ] - | DocumentedSrc.Nested { code; doc; anchor; _ } -> - Accum [ (`N code, doc, anchor) ] - | _ -> Stop_and_keep) + | Subpage { content = { title = _; header = _; items; url = _ }; _ } -> + let content = + if items = [] then paragraph line_break + else item items args (nesting_level + 1) in - let f (content, doc, (anchor : Odoc_document.Url.t option)) = - let content = - let nesting_level = nesting_level + 1 in - match content with - | `D code (* for record fields and polymorphic variants *) -> - item_heading nesting_level (inline code args) - | `N l (* for constructors *) -> - let c, rest = take_code l in - blocks - (item_heading nesting_level (source_code c args)) - (continue rest) - in - let item = blocks content (block args doc) in - if args.generate_links then - let anchor = - match anchor with Some a -> a.anchor | None -> "" - in - blocks (paragraph (anchor' anchor)) item - else item - in - blocks (fold_blocks f lines) (continue rest)) + content +++ continue rest + | Documented { code; doc; anchor; _ } -> + documented args nesting_level (`D code) doc anchor +++ continue rest + | Nested { code; doc; anchor; _ } -> + documented args nesting_level (`N code) doc anchor +++ continue rest) -and subpage { title = _; header = _; items; url = _ } args nesting_level = - let content = items in - let subpage' body = if content = [] then paragraph line_break else body in - subpage' @@ item content args nesting_level +and documented args nesting_level content doc anchor = + let content = + let nesting_level = nesting_level + 1 in + match content with + | `D code (* for record fields and polymorphic variants *) -> + item_heading nesting_level (inline code args) + | `N l (* for constructors *) -> + let c, rest = take_code l in + item_heading nesting_level (source_code c args) + +++ documented_src rest args nesting_level + in + let item = blocks content (block args doc) in + if args.generate_links then + let anchor = + match anchor with Some a -> a.Url.Anchor.anchor | None -> "" + in + blocks (paragraph (anchor' anchor)) item + else item and item (l : Item.t list) args nesting_level = match l with diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 227e3f7d6e..8ffa95141f 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -40,7 +40,7 @@ _bar_ -######    `;int : a` +######      `;int : a` } @@ -64,7 +64,7 @@ foo -######    `;int : a` +######      `;int : a` } -> unit [gadt](#type-gadt) diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index e6c7b6b455..6eb73f801e 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -24,7 +24,7 @@ Module `Stop_dead_link_doc` -######    field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t) ; +######      field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t) ; } From 7449b4ad057d720c8dab910ff751f2c566b8fac0 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 7 Feb 2022 16:00:49 +0100 Subject: [PATCH 26/38] Fix spacing after quote blocks Also: - Make sure to terminate the last line of the document. - Avoid using 'String.split_on_char' for compat --- src/markdown/markup.ml | 27 ++++-- test/generators/markdown/Alias.X.md | 3 +- test/generators/markdown/Alias.md | 2 +- test/generators/markdown/Bugs.md | 4 +- .../Bugs_post_406.class-type-let_open.md | 2 +- .../markdown/Bugs_post_406.let_open'.md | 2 +- test/generators/markdown/Bugs_post_406.md | 2 +- .../markdown/Class.class-type-empty.md | 2 +- .../Class.class-type-empty_virtual.md | 2 +- .../markdown/Class.class-type-mutually.md | 2 +- .../markdown/Class.class-type-polymorphic.md | 2 +- .../markdown/Class.class-type-recursive.md | 2 +- .../markdown/Class.empty_virtual'.md | 2 +- test/generators/markdown/Class.md | 2 +- test/generators/markdown/Class.mutually'.md | 2 +- .../generators/markdown/Class.polymorphic'.md | 2 +- test/generators/markdown/Class.recursive'.md | 2 +- test/generators/markdown/External.md | 3 +- .../markdown/Functor.F1.argument-1-Arg.md | 2 +- test/generators/markdown/Functor.F1.md | 2 +- .../markdown/Functor.F2.argument-1-Arg.md | 2 +- .../markdown/Functor.F3.argument-1-Arg.md | 2 +- .../markdown/Functor.F4.argument-1-Arg.md | 2 +- test/generators/markdown/Functor.F4.md | 2 +- test/generators/markdown/Functor.F5.md | 2 +- test/generators/markdown/Functor.md | 2 +- .../markdown/Functor.module-type-S.md | 2 +- .../Functor.module-type-S1.argument-1-_.md | 2 +- .../markdown/Functor.module-type-S1.md | 2 +- .../markdown/Functor2.X.argument-1-Y.md | 2 +- .../markdown/Functor2.X.argument-2-Z.md | 2 +- test/generators/markdown/Functor2.X.md | 2 - test/generators/markdown/Functor2.md | 2 +- .../markdown/Functor2.module-type-S.md | 2 +- .../Functor2.module-type-XF.argument-1-Y.md | 2 +- .../Functor2.module-type-XF.argument-2-Z.md | 2 +- .../markdown/Functor2.module-type-XF.md | 2 - .../markdown/Include.module-type-Inlined.md | 2 +- .../Include.module-type-Not_inlined.md | 2 +- ...lude.module-type-Not_inlined_and_closed.md | 2 +- ...lude.module-type-Not_inlined_and_opened.md | 2 +- test/generators/markdown/Include2.Y.md | 2 +- test/generators/markdown/Include2.md | 3 +- test/generators/markdown/Include_sections.md | 5 +- .../Include_sections.module-type-Something.md | 5 +- test/generators/markdown/Interlude.md | 7 +- test/generators/markdown/Labels.A.md | 2 +- test/generators/markdown/Labels.c.md | 2 +- .../markdown/Labels.class-type-cs.md | 2 +- test/generators/markdown/Labels.md | 21 +++-- .../markdown/Labels.module-type-S.md | 2 +- test/generators/markdown/Markup.X.md | 2 +- test/generators/markdown/Markup.Y.md | 2 +- test/generators/markdown/Markup.md | 22 +++-- test/generators/markdown/Module.M'.md | 2 +- test/generators/markdown/Module.Mutually.md | 2 +- test/generators/markdown/Module.Recursive.md | 2 +- test/generators/markdown/Module.md | 4 +- .../markdown/Module.module-type-S.M.md | 2 +- .../markdown/Module.module-type-S.md | 2 +- .../markdown/Module.module-type-S3.M.md | 2 +- .../markdown/Module.module-type-S3.md | 4 +- .../markdown/Module.module-type-S4.M.md | 2 +- .../markdown/Module.module-type-S4.md | 2 +- .../markdown/Module.module-type-S5.M.md | 2 +- .../markdown/Module.module-type-S5.md | 2 +- .../markdown/Module.module-type-S6.M.md | 2 +- .../markdown/Module.module-type-S6.md | 2 +- .../markdown/Module.module-type-S8.md | 2 +- .../markdown/Module.module-type-S9.md | 2 +- test/generators/markdown/Module_type_alias.md | 1 - .../Module_type_alias.module-type-A.md | 2 +- ...e_type_alias.module-type-B.argument-1-C.md | 2 +- .../Module_type_alias.module-type-B.md | 2 +- ...e_type_alias.module-type-E.argument-1-F.md | 2 +- ...e_type_alias.module-type-E.argument-2-C.md | 2 +- .../Module_type_alias.module-type-E.md | 2 +- ...e_type_alias.module-type-G.argument-1-H.md | 2 +- .../Module_type_alias.module-type-G.md | 2 +- .../markdown/Module_type_subst.Basic.md | 2 +- ...Module_type_subst.Basic.module-type-a.M.md | 2 +- .../Module_type_subst.Basic.module-type-a.md | 3 +- ...Module_type_subst.Basic.module-type-c.M.md | 2 +- .../Module_type_subst.Basic.module-type-c.md | 2 +- .../Module_type_subst.Basic.module-type-u.md | 2 +- ...subst.Basic.module-type-u.module-type-T.md | 2 +- ...odule_type_subst.Basic.module-type-u2.M.md | 2 +- .../Module_type_subst.Basic.module-type-u2.md | 2 +- ...ubst.Basic.module-type-u2.module-type-T.md | 2 +- ...e_type_subst.Basic.module-type-with_2.M.md | 2 +- ...ule_type_subst.Basic.module-type-with_2.md | 2 +- ....Basic.module-type-with_2.module-type-T.md | 2 +- .../markdown/Module_type_subst.Local.md | 4 +- .../Module_type_subst.Local.module-type-s.md | 2 +- .../markdown/Module_type_subst.Nested.md | 2 +- ..._type_subst.Nested.module-type-nested.N.md | 2 +- ...sted.module-type-nested.N.module-type-t.md | 2 +- ...le_type_subst.Nested.module-type-nested.md | 2 +- ...ule_type_subst.Nested.module-type-with_.md | 2 +- ...e_subst.Nested.module-type-with_subst.N.md | 2 +- ...ype_subst.Nested.module-type-with_subst.md | 2 +- .../markdown/Module_type_subst.Structural.md | 2 +- ...ule_type_subst.Structural.module-type-u.md | 2 +- ....Structural.module-type-u.module-type-a.md | 2 +- ...dule-type-u.module-type-a.module-type-b.md | 2 +- ...dule-type-a.module-type-b.module-type-c.md | 2 +- ...ule_type_subst.Structural.module-type-w.md | 2 +- ....Structural.module-type-w.module-type-a.md | 2 +- ...dule-type-w.module-type-a.module-type-b.md | 2 +- ...dule-type-a.module-type-b.module-type-c.md | 2 +- test/generators/markdown/Module_type_subst.md | 2 +- .../Module_type_subst.module-type-s.md | 2 +- .../markdown/Nested.F.argument-1-Arg1.md | 3 +- .../markdown/Nested.F.argument-2-Arg2.md | 2 +- test/generators/markdown/Nested.F.md | 3 +- test/generators/markdown/Nested.X.md | 3 +- test/generators/markdown/Nested.inherits.md | 2 +- test/generators/markdown/Nested.md | 2 +- .../markdown/Nested.module-type-Y.md | 3 +- test/generators/markdown/Nested.z.md | 3 - .../markdown/Ocamlary.Aliases.Foo.md | 2 +- .../markdown/Ocamlary.Aliases.P1.md | 2 +- .../markdown/Ocamlary.Aliases.Std.md | 4 - test/generators/markdown/Ocamlary.Aliases.md | 14 --- .../markdown/Ocamlary.CanonicalTest.Base.md | 2 +- .../Ocamlary.CanonicalTest.Base_Tests.md | 3 - .../Ocamlary.CanonicalTest.List_modif.md | 1 - .../markdown/Ocamlary.CanonicalTest.md | 2 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 3 +- .../Ocamlary.CollectionModule.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../markdown/Ocamlary.CollectionModule.md | 3 +- test/generators/markdown/Ocamlary.Dep1.X.Y.md | 2 +- test/generators/markdown/Ocamlary.Dep1.X.md | 2 +- test/generators/markdown/Ocamlary.Dep1.md | 2 +- .../markdown/Ocamlary.Dep1.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.Dep11.md | 2 +- .../markdown/Ocamlary.Dep11.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep12.argument-1-Arg.md | 2 +- test/generators/markdown/Ocamlary.Dep13.md | 2 +- .../markdown/Ocamlary.Dep2.argument-1-Arg.md | 2 +- test/generators/markdown/Ocamlary.Dep3.md | 2 +- test/generators/markdown/Ocamlary.Dep4.X.md | 2 +- test/generators/markdown/Ocamlary.Dep4.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-S.X.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-S.Y.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep4.module-type-T.md | 2 +- test/generators/markdown/Ocamlary.Dep5.Z.md | 1 - ...ary.Dep5.argument-1-Arg.module-type-S.Y.md | 2 +- ...mlary.Dep5.argument-1-Arg.module-type-S.md | 3 +- test/generators/markdown/Ocamlary.Dep5.md | 2 +- test/generators/markdown/Ocamlary.Dep6.X.Y.md | 2 +- test/generators/markdown/Ocamlary.Dep6.X.md | 3 +- test/generators/markdown/Ocamlary.Dep6.md | 2 +- .../markdown/Ocamlary.Dep6.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep6.module-type-T.Y.md | 2 +- .../markdown/Ocamlary.Dep6.module-type-T.md | 3 +- test/generators/markdown/Ocamlary.Dep7.M.md | 1 - .../Ocamlary.Dep7.argument-1-Arg.X.md | 1 - .../markdown/Ocamlary.Dep7.argument-1-Arg.md | 2 +- ...mlary.Dep7.argument-1-Arg.module-type-T.md | 1 - test/generators/markdown/Ocamlary.Dep7.md | 2 +- test/generators/markdown/Ocamlary.Dep8.md | 2 +- .../markdown/Ocamlary.Dep8.module-type-T.md | 2 +- .../markdown/Ocamlary.Dep9.argument-1-X.md | 2 +- .../Ocamlary.DoubleInclude1.DoubleInclude2.md | 2 +- .../markdown/Ocamlary.DoubleInclude1.md | 2 +- .../Ocamlary.DoubleInclude3.DoubleInclude2.md | 2 +- .../markdown/Ocamlary.DoubleInclude3.md | 2 +- test/generators/markdown/Ocamlary.Empty.md | 2 +- test/generators/markdown/Ocamlary.ExtMod.md | 3 +- ...1-Collection.InnerModuleA.InnerModuleA'.md | 3 +- ...peOf.argument-1-Collection.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- ...ary.FunctorTypeOf.argument-1-Collection.md | 3 +- .../markdown/Ocamlary.FunctorTypeOf.md | 3 +- ...mlary.IncludeInclude1.IncludeInclude2_M.md | 2 +- .../markdown/Ocamlary.IncludeInclude1.md | 2 +- ...udeInclude1.module-type-IncludeInclude2.md | 2 +- .../markdown/Ocamlary.IncludeInclude2_M.md | 2 +- .../generators/markdown/Ocamlary.IncludedA.md | 2 +- test/generators/markdown/Ocamlary.M.md | 2 +- .../markdown/Ocamlary.ModuleWithSignature.md | 2 +- .../Ocamlary.ModuleWithSignatureAlias.md | 2 +- test/generators/markdown/Ocamlary.One.md | 2 +- .../markdown/Ocamlary.Only_a_module.md | 2 +- ...Recollection.InnerModuleA.InnerModuleA'.md | 3 +- .../Ocamlary.Recollection.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- ...argument-1-C.InnerModuleA.InnerModuleA'.md | 3 +- ....Recollection.argument-1-C.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../Ocamlary.Recollection.argument-1-C.md | 3 +- .../markdown/Ocamlary.Recollection.md | 5 +- test/generators/markdown/Ocamlary.With10.md | 2 +- .../Ocamlary.With10.module-type-T.M.md | 2 +- test/generators/markdown/Ocamlary.With2.md | 2 +- .../markdown/Ocamlary.With2.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.With3.N.md | 2 +- test/generators/markdown/Ocamlary.With3.md | 3 +- test/generators/markdown/Ocamlary.With4.N.md | 2 +- test/generators/markdown/Ocamlary.With4.md | 2 +- test/generators/markdown/Ocamlary.With5.N.md | 2 +- test/generators/markdown/Ocamlary.With5.md | 2 +- .../markdown/Ocamlary.With5.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.With6.md | 2 +- .../markdown/Ocamlary.With6.module-type-T.md | 2 +- .../markdown/Ocamlary.With7.argument-1-X.md | 2 +- test/generators/markdown/Ocamlary.With9.md | 2 +- .../markdown/Ocamlary.With9.module-type-S.md | 2 +- .../markdown/Ocamlary.empty_class.md | 2 +- test/generators/markdown/Ocamlary.md | 88 ++++++------------- ...ule-type-A.Q.InnerModuleA.InnerModuleA'.md | 3 +- .../Ocamlary.module-type-A.Q.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../markdown/Ocamlary.module-type-A.Q.md | 3 +- .../markdown/Ocamlary.module-type-A.md | 2 +- ...ule-type-B.Q.InnerModuleA.InnerModuleA'.md | 3 +- .../Ocamlary.module-type-B.Q.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../markdown/Ocamlary.module-type-B.Q.md | 3 +- .../markdown/Ocamlary.module-type-B.md | 2 +- ...ule-type-C.Q.InnerModuleA.InnerModuleA'.md | 3 +- .../Ocamlary.module-type-C.Q.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../markdown/Ocamlary.module-type-C.Q.md | 3 +- .../markdown/Ocamlary.module-type-C.md | 3 + ...e-COLLECTION.InnerModuleA.InnerModuleA'.md | 3 +- ...ary.module-type-COLLECTION.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../Ocamlary.module-type-COLLECTION.md | 3 +- .../markdown/Ocamlary.module-type-Empty.md | 2 +- .../markdown/Ocamlary.module-type-EmptySig.md | 2 +- .../Ocamlary.module-type-IncludeInclude2.md | 2 +- .../Ocamlary.module-type-IncludeModuleType.md | 1 + .../Ocamlary.module-type-IncludedB.md | 2 +- .../markdown/Ocamlary.module-type-M.md | 2 +- ...e-type-MMM.C.InnerModuleA.InnerModuleA'.md | 3 +- ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- .../markdown/Ocamlary.module-type-MMM.C.md | 3 +- .../markdown/Ocamlary.module-type-MMM.md | 2 +- .../Ocamlary.module-type-MissingComment.md | 2 +- .../Ocamlary.module-type-NestedInclude1.md | 2 +- ...stedInclude1.module-type-NestedInclude2.md | 2 +- .../Ocamlary.module-type-NestedInclude2.md | 2 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 3 +- ...le-type-RecollectionModule.InnerModuleA.md | 3 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 3 +- ...Ocamlary.module-type-RecollectionModule.md | 5 +- .../Ocamlary.module-type-SigForMod.Inner.md | 2 +- ...-type-SigForMod.Inner.module-type-Empty.md | 2 +- .../Ocamlary.module-type-SigForMod.md | 2 +- .../markdown/Ocamlary.module-type-SuperSig.md | 2 +- ...dule-type-SuperSig.module-type-EmptySig.md | 2 +- ...ry.module-type-SuperSig.module-type-One.md | 2 +- ...SuperSig.module-type-SubSigA.SubSigAMod.md | 2 +- ...odule-type-SuperSig.module-type-SubSigA.md | 2 +- ...odule-type-SuperSig.module-type-SubSigB.md | 2 +- ...dule-type-SuperSig.module-type-SuperSig.md | 2 +- ...camlary.module-type-ToInclude.IncludedA.md | 2 +- .../Ocamlary.module-type-ToInclude.md | 2 +- ...le-type-ToInclude.module-type-IncludedB.md | 2 +- .../markdown/Ocamlary.module-type-TypeExt.md | 1 - .../markdown/Ocamlary.module-type-With1.M.md | 2 +- .../markdown/Ocamlary.module-type-With11.md | 3 +- .../markdown/Ocamlary.module-type-With8.M.md | 3 +- .../markdown/Ocamlary.module-type-With8.md | 2 +- .../markdown/Ocamlary.two_method_class.md | 1 - test/generators/markdown/Recent.X.md | 3 - test/generators/markdown/Recent.Z.Y.X.md | 2 +- test/generators/markdown/Recent.Z.Y.md | 2 +- test/generators/markdown/Recent.Z.md | 2 +- test/generators/markdown/Recent.md | 6 +- .../markdown/Recent.module-type-PolyS.md | 2 +- .../markdown/Recent.module-type-S.md | 2 +- .../Recent.module-type-S1.argument-1-_.md | 2 +- .../markdown/Recent.module-type-S1.md | 2 +- test/generators/markdown/Recent_impl.B.md | 2 +- test/generators/markdown/Recent_impl.Foo.A.md | 2 +- test/generators/markdown/Recent_impl.Foo.B.md | 2 +- test/generators/markdown/Recent_impl.Foo.md | 2 +- ...ecent_impl.module-type-S.F.argument-1-_.md | 2 +- .../markdown/Recent_impl.module-type-S.F.md | 2 +- .../markdown/Recent_impl.module-type-S.X.md | 2 +- test/generators/markdown/Section.md | 3 +- test/generators/markdown/Stop.md | 1 - .../markdown/Stop_dead_link_doc.Foo.md | 2 +- .../generators/markdown/Stop_dead_link_doc.md | 2 +- .../markdown/Toplevel_comments.Alias.md | 2 +- .../Toplevel_comments.Comments_on_open.M.md | 2 +- .../Toplevel_comments.Comments_on_open.md | 2 +- .../Toplevel_comments.Include_inline'.md | 2 +- .../Toplevel_comments.Include_inline.md | 2 +- .../markdown/Toplevel_comments.M''.md | 2 +- .../markdown/Toplevel_comments.M'.md | 2 +- .../markdown/Toplevel_comments.M.md | 2 +- .../Toplevel_comments.Ref_in_synopsis.md | 2 +- .../markdown/Toplevel_comments.c1.md | 2 +- .../markdown/Toplevel_comments.c2.md | 2 +- .../Toplevel_comments.class-type-ct.md | 2 +- test/generators/markdown/Toplevel_comments.md | 2 +- ..._comments.module-type-Include_inline_T'.md | 2 +- ...l_comments.module-type-Include_inline_T.md | 2 +- .../Toplevel_comments.module-type-T.md | 2 +- test/generators/markdown/Type.md | 33 +------ .../generators/markdown/Type.module-type-X.md | 2 +- test/generators/markdown/Val.md | 5 +- test/generators/markdown/mld.md | 2 +- 310 files changed, 371 insertions(+), 525 deletions(-) diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 0ff1c7619f..747b1d9ee7 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -81,17 +81,26 @@ let heading level i = let hashes = make_hashes level in Block (String hashes ++ i) +(** [split_on_char] is not available on [< 4.04]. *) +let rec iter_lines f s i = + try + let i' = String.index_from s i '\n' in + f (String.sub s i (i' - i)); + iter_lines f s (i' + 1) + with Not_found -> + let len = String.length s in + if i < len then f (String.sub s i (len - i)) + (** Every lines that [f] formats are prefixed and written in [sink]. Inefficient. *) let with_prefixed_formatter prefix sink f = let s = Format.asprintf "%t" f in - String.split_on_char '\n' s - |> List.iter (fun l -> Format.fprintf sink "%s%s@\n" prefix l) + iter_lines (Format.fprintf sink "%s%s@\n" prefix) s 0 let pp_list_item fmt list_type (b : blocks) n pp_blocks = match list_type with - | Unordered -> Format.fprintf fmt "- @[%a@]" pp_blocks b - | Ordered -> Format.fprintf fmt "%d. @[%a@]" (n + 1) pp_blocks b + | Unordered -> Format.fprintf fmt "- @[%a@]@\n" pp_blocks b + | Ordered -> Format.fprintf fmt "%d. @[%a@]@\n" (n + 1) pp_blocks b let rec pp_inlines fmt i = match i with @@ -111,10 +120,12 @@ let rec pp_blocks fmt b = match b with | ConcatB (Block Noop, b) | ConcatB (b, Block Noop) -> pp_blocks fmt b | ConcatB (above, below) -> - Format.fprintf fmt "%a@\n@\n%a" pp_blocks above pp_blocks below - | Block i -> pp_inlines fmt i + Format.fprintf fmt "%a@\n%a" pp_blocks above pp_blocks below + | Block i -> + pp_inlines fmt i; + Format.fprintf fmt "@\n" | CodeBlock i -> Format.fprintf fmt "```@\n%a@\n```" pp_inlines i - | Block_separator -> Format.fprintf fmt "---" + | Block_separator -> Format.fprintf fmt "---@\n" | List (list_type, l) -> let rec pp_list n l = match l with @@ -122,7 +133,7 @@ let rec pp_blocks fmt b = | [ x ] -> pp_list_item fmt list_type x n pp_blocks | x :: rest -> pp_list_item fmt list_type x n pp_blocks; - Format.fprintf fmt "@\n@\n"; + Format.fprintf fmt "@\n"; pp_list (n + 1) rest in pp_list 0 l diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md index 26543a75cd..e7dc9b97f6 100644 --- a/test/generators/markdown/Alias.X.md +++ b/test/generators/markdown/Alias.X.md @@ -10,5 +10,4 @@ Module `Alias.X` > int - -Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' \ No newline at end of file +Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' diff --git a/test/generators/markdown/Alias.md b/test/generators/markdown/Alias.md index 8e7b7084d5..33fd92cbd1 100644 --- a/test/generators/markdown/Alias.md +++ b/test/generators/markdown/Alias.md @@ -4,4 +4,4 @@ Module `Alias` -###### module [X](Alias.X.md) \ No newline at end of file +###### module [X](Alias.X.md) diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index 637d9d8cbd..1ce9bca536 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -8,12 +8,10 @@ Module `Bugs` > 'a option - ###### val foo : > ? bar : 'a -> unit -> unit - -Triggers an assertion failure when [https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) is not fixed. \ No newline at end of file +Triggers an assertion failure when [https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) is not fixed. diff --git a/test/generators/markdown/Bugs_post_406.class-type-let_open.md b/test/generators/markdown/Bugs_post_406.class-type-let_open.md index aec72c2e79..92edbb87a4 100644 --- a/test/generators/markdown/Bugs_post_406.class-type-let_open.md +++ b/test/generators/markdown/Bugs_post_406.class-type-let_open.md @@ -2,4 +2,4 @@ Bugs_post_406 let_open -Class type `Bugs_post_406.let_open` \ No newline at end of file +Class type `Bugs_post_406.let_open` diff --git a/test/generators/markdown/Bugs_post_406.let_open'.md b/test/generators/markdown/Bugs_post_406.let_open'.md index c879c31fad..d96ddd9b21 100644 --- a/test/generators/markdown/Bugs_post_406.let_open'.md +++ b/test/generators/markdown/Bugs_post_406.let_open'.md @@ -2,4 +2,4 @@ Bugs_post_406 let_open' -Class `Bugs_post_406.let_open'` \ No newline at end of file +Class `Bugs_post_406.let_open'` diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index eb7f31ff75..6b7b6e3ce4 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -10,4 +10,4 @@ Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added -###### class [let_open'](Bugs_post_406.let_open'.md) \ No newline at end of file +###### class [let_open'](Bugs_post_406.let_open'.md) diff --git a/test/generators/markdown/Class.class-type-empty.md b/test/generators/markdown/Class.class-type-empty.md index 18f58446e9..9c44f41e09 100644 --- a/test/generators/markdown/Class.class-type-empty.md +++ b/test/generators/markdown/Class.class-type-empty.md @@ -2,4 +2,4 @@ Class empty -Class type `Class.empty` \ No newline at end of file +Class type `Class.empty` diff --git a/test/generators/markdown/Class.class-type-empty_virtual.md b/test/generators/markdown/Class.class-type-empty_virtual.md index 1ef5cdce0b..0ac705802e 100644 --- a/test/generators/markdown/Class.class-type-empty_virtual.md +++ b/test/generators/markdown/Class.class-type-empty_virtual.md @@ -2,4 +2,4 @@ Class empty_virtual -Class type `Class.empty_virtual` \ No newline at end of file +Class type `Class.empty_virtual` diff --git a/test/generators/markdown/Class.class-type-mutually.md b/test/generators/markdown/Class.class-type-mutually.md index ea5ff43f3e..1b5564c8bf 100644 --- a/test/generators/markdown/Class.class-type-mutually.md +++ b/test/generators/markdown/Class.class-type-mutually.md @@ -2,4 +2,4 @@ Class mutually -Class type `Class.mutually` \ No newline at end of file +Class type `Class.mutually` diff --git a/test/generators/markdown/Class.class-type-polymorphic.md b/test/generators/markdown/Class.class-type-polymorphic.md index c17a11a9a0..0ce940c8d3 100644 --- a/test/generators/markdown/Class.class-type-polymorphic.md +++ b/test/generators/markdown/Class.class-type-polymorphic.md @@ -2,4 +2,4 @@ Class polymorphic -Class type `Class.polymorphic` \ No newline at end of file +Class type `Class.polymorphic` diff --git a/test/generators/markdown/Class.class-type-recursive.md b/test/generators/markdown/Class.class-type-recursive.md index bb7b6d3bad..ff9f483196 100644 --- a/test/generators/markdown/Class.class-type-recursive.md +++ b/test/generators/markdown/Class.class-type-recursive.md @@ -2,4 +2,4 @@ Class recursive -Class type `Class.recursive` \ No newline at end of file +Class type `Class.recursive` diff --git a/test/generators/markdown/Class.empty_virtual'.md b/test/generators/markdown/Class.empty_virtual'.md index d9ec1f08e3..f4d83f7e34 100644 --- a/test/generators/markdown/Class.empty_virtual'.md +++ b/test/generators/markdown/Class.empty_virtual'.md @@ -2,4 +2,4 @@ Class empty_virtual' -Class `Class.empty_virtual'` \ No newline at end of file +Class `Class.empty_virtual'` diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md index fad6889d8c..e1d8761c53 100644 --- a/test/generators/markdown/Class.md +++ b/test/generators/markdown/Class.md @@ -36,4 +36,4 @@ Module `Class` -###### class 'a [polymorphic'](Class.polymorphic'.md) \ No newline at end of file +###### class 'a [polymorphic'](Class.polymorphic'.md) diff --git a/test/generators/markdown/Class.mutually'.md b/test/generators/markdown/Class.mutually'.md index 3b00c21b8b..020c07874d 100644 --- a/test/generators/markdown/Class.mutually'.md +++ b/test/generators/markdown/Class.mutually'.md @@ -2,4 +2,4 @@ Class mutually' -Class `Class.mutually'` \ No newline at end of file +Class `Class.mutually'` diff --git a/test/generators/markdown/Class.polymorphic'.md b/test/generators/markdown/Class.polymorphic'.md index fc222f0fcd..e01816e029 100644 --- a/test/generators/markdown/Class.polymorphic'.md +++ b/test/generators/markdown/Class.polymorphic'.md @@ -2,4 +2,4 @@ Class polymorphic' -Class `Class.polymorphic'` \ No newline at end of file +Class `Class.polymorphic'` diff --git a/test/generators/markdown/Class.recursive'.md b/test/generators/markdown/Class.recursive'.md index 0ce70ddcb9..03a47c367e 100644 --- a/test/generators/markdown/Class.recursive'.md +++ b/test/generators/markdown/Class.recursive'.md @@ -2,4 +2,4 @@ Class recursive' -Class `Class.recursive'` \ No newline at end of file +Class `Class.recursive'` diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md index c03ff524e6..e28b1c5a0e 100644 --- a/test/generators/markdown/External.md +++ b/test/generators/markdown/External.md @@ -8,5 +8,4 @@ Module `External` > unit -> unit - -Foo _bar_ . \ No newline at end of file +Foo _bar_ . diff --git a/test/generators/markdown/Functor.F1.argument-1-Arg.md b/test/generators/markdown/Functor.F1.argument-1-Arg.md index 87466ccdc8..1fb180615b 100644 --- a/test/generators/markdown/Functor.F1.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F1.argument-1-Arg.md @@ -8,4 +8,4 @@ Parameter `F1.1-Arg` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.F1.md b/test/generators/markdown/Functor.F1.md index 5a0fbfb033..3fdfa3f332 100644 --- a/test/generators/markdown/Functor.F1.md +++ b/test/generators/markdown/Functor.F1.md @@ -14,4 +14,4 @@ Module `Functor.F1` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.F2.argument-1-Arg.md b/test/generators/markdown/Functor.F2.argument-1-Arg.md index 0aa6e67c42..c31ca5c063 100644 --- a/test/generators/markdown/Functor.F2.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F2.argument-1-Arg.md @@ -8,4 +8,4 @@ Parameter `F2.1-Arg` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.F3.argument-1-Arg.md b/test/generators/markdown/Functor.F3.argument-1-Arg.md index e1cf8e8980..225510152d 100644 --- a/test/generators/markdown/Functor.F3.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F3.argument-1-Arg.md @@ -8,4 +8,4 @@ Parameter `F3.1-Arg` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.F4.argument-1-Arg.md b/test/generators/markdown/Functor.F4.argument-1-Arg.md index 98e5cd207c..76a905ceff 100644 --- a/test/generators/markdown/Functor.F4.argument-1-Arg.md +++ b/test/generators/markdown/Functor.F4.argument-1-Arg.md @@ -8,4 +8,4 @@ Parameter `F4.1-Arg` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.F4.md b/test/generators/markdown/Functor.F4.md index df2ab891fa..f6755cd5b2 100644 --- a/test/generators/markdown/Functor.F4.md +++ b/test/generators/markdown/Functor.F4.md @@ -14,4 +14,4 @@ Module `Functor.F4` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.F5.md b/test/generators/markdown/Functor.F5.md index 4033906922..702b4abbd1 100644 --- a/test/generators/markdown/Functor.F5.md +++ b/test/generators/markdown/Functor.F5.md @@ -10,4 +10,4 @@ Module `Functor.F5` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.md b/test/generators/markdown/Functor.md index b80f8b9757..64e5a4d868 100644 --- a/test/generators/markdown/Functor.md +++ b/test/generators/markdown/Functor.md @@ -28,4 +28,4 @@ Module `Functor` -###### module [F5](Functor.F5.md) \ No newline at end of file +###### module [F5](Functor.F5.md) diff --git a/test/generators/markdown/Functor.module-type-S.md b/test/generators/markdown/Functor.module-type-S.md index b7de7ea78a..4f4486848a 100644 --- a/test/generators/markdown/Functor.module-type-S.md +++ b/test/generators/markdown/Functor.module-type-S.md @@ -6,4 +6,4 @@ Module type `Functor.S` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.module-type-S1.argument-1-_.md b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md index 17485b9375..612d8d7f9c 100644 --- a/test/generators/markdown/Functor.module-type-S1.argument-1-_.md +++ b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md @@ -8,4 +8,4 @@ Parameter `S1.1-_` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor.module-type-S1.md b/test/generators/markdown/Functor.module-type-S1.md index 80dafac2b0..211952936f 100644 --- a/test/generators/markdown/Functor.module-type-S1.md +++ b/test/generators/markdown/Functor.module-type-S1.md @@ -14,4 +14,4 @@ Module type `Functor.S1` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor2.X.argument-1-Y.md b/test/generators/markdown/Functor2.X.argument-1-Y.md index 1ce8ac974e..13051940d1 100644 --- a/test/generators/markdown/Functor2.X.argument-1-Y.md +++ b/test/generators/markdown/Functor2.X.argument-1-Y.md @@ -8,4 +8,4 @@ Parameter `X.1-Y` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor2.X.argument-2-Z.md b/test/generators/markdown/Functor2.X.argument-2-Z.md index 34ddf9bfc2..10cb9494c9 100644 --- a/test/generators/markdown/Functor2.X.argument-2-Z.md +++ b/test/generators/markdown/Functor2.X.argument-2-Z.md @@ -8,4 +8,4 @@ Parameter `X.2-Z` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor2.X.md b/test/generators/markdown/Functor2.X.md index 11478923bf..b17ffae163 100644 --- a/test/generators/markdown/Functor2.X.md +++ b/test/generators/markdown/Functor2.X.md @@ -22,14 +22,12 @@ Module `Functor2.X` > [Y.t](Functor2.X.argument-1-Y.md#type-t) - ###### type z_t = > [Z.t](Functor2.X.argument-2-Z.md#type-t) - ###### type x_t = diff --git a/test/generators/markdown/Functor2.md b/test/generators/markdown/Functor2.md index 8cce76edf2..d7a05741b4 100644 --- a/test/generators/markdown/Functor2.md +++ b/test/generators/markdown/Functor2.md @@ -12,4 +12,4 @@ Module `Functor2` -###### module type [XF](Functor2.module-type-XF.md) \ No newline at end of file +###### module type [XF](Functor2.module-type-XF.md) diff --git a/test/generators/markdown/Functor2.module-type-S.md b/test/generators/markdown/Functor2.module-type-S.md index 21b1fcb87f..39bfc705a1 100644 --- a/test/generators/markdown/Functor2.module-type-S.md +++ b/test/generators/markdown/Functor2.module-type-S.md @@ -6,4 +6,4 @@ Module type `Functor2.S` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md b/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md index 65b39521cf..6866b9b635 100644 --- a/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md +++ b/test/generators/markdown/Functor2.module-type-XF.argument-1-Y.md @@ -8,4 +8,4 @@ Parameter `XF.1-Y` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md b/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md index 3f8789aa9f..d53ceaa922 100644 --- a/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md +++ b/test/generators/markdown/Functor2.module-type-XF.argument-2-Z.md @@ -8,4 +8,4 @@ Parameter `XF.2-Z` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Functor2.module-type-XF.md b/test/generators/markdown/Functor2.module-type-XF.md index 0cc97253fa..665e93a7da 100644 --- a/test/generators/markdown/Functor2.module-type-XF.md +++ b/test/generators/markdown/Functor2.module-type-XF.md @@ -22,14 +22,12 @@ Module type `Functor2.XF` > [Y.t](Functor2.module-type-XF.argument-1-Y.md#type-t) - ###### type z_t = > [Z.t](Functor2.module-type-XF.argument-2-Z.md#type-t) - ###### type x_t = diff --git a/test/generators/markdown/Include.module-type-Inlined.md b/test/generators/markdown/Include.module-type-Inlined.md index 45194f8982..60679c9de3 100644 --- a/test/generators/markdown/Include.module-type-Inlined.md +++ b/test/generators/markdown/Include.module-type-Inlined.md @@ -6,4 +6,4 @@ Module type `Include.Inlined` -###### type u \ No newline at end of file +###### type u diff --git a/test/generators/markdown/Include.module-type-Not_inlined.md b/test/generators/markdown/Include.module-type-Not_inlined.md index 5736e3aeaa..0c44e1ccb8 100644 --- a/test/generators/markdown/Include.module-type-Not_inlined.md +++ b/test/generators/markdown/Include.module-type-Not_inlined.md @@ -6,4 +6,4 @@ Module type `Include.Not_inlined` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md b/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md index fe207ddde5..f1ba9dc490 100644 --- a/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md +++ b/test/generators/markdown/Include.module-type-Not_inlined_and_closed.md @@ -6,4 +6,4 @@ Module type `Include.Not_inlined_and_closed` -###### type v \ No newline at end of file +###### type v diff --git a/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md b/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md index e739980268..5052c458d3 100644 --- a/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md +++ b/test/generators/markdown/Include.module-type-Not_inlined_and_opened.md @@ -6,4 +6,4 @@ Module type `Include.Not_inlined_and_opened` -###### type w \ No newline at end of file +###### type w diff --git a/test/generators/markdown/Include2.Y.md b/test/generators/markdown/Include2.Y.md index 83cefa7611..aff8a6729b 100644 --- a/test/generators/markdown/Include2.Y.md +++ b/test/generators/markdown/Include2.Y.md @@ -8,4 +8,4 @@ Top-comment of Y. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index 0d7f501d4d..adbe9eda1f 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -16,7 +16,6 @@ Comment about X that should not appear when including X below. > int - ###### module [Y](Include2.Y.md) @@ -31,4 +30,4 @@ The `include Y` below should have the synopsis from `Y` 's top-comment attached -###### module [Y_include_doc](Include2.Y_include_doc.md) \ No newline at end of file +###### module [Y_include_doc](Include2.Y_include_doc.md) diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index 39094738b3..593cee3b88 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -64,7 +64,6 @@ And let's include it again, but without inlining it this time: the ToC shouldn't > unit - # Something 1 foo @@ -75,7 +74,6 @@ foo > unit - ## Something 2 --- @@ -86,9 +84,8 @@ foo > unit - foo bar # Something 1-bis -Some text. \ No newline at end of file +Some text. diff --git a/test/generators/markdown/Include_sections.module-type-Something.md b/test/generators/markdown/Include_sections.module-type-Something.md index 08f695af62..6cbef4248e 100644 --- a/test/generators/markdown/Include_sections.module-type-Something.md +++ b/test/generators/markdown/Include_sections.module-type-Something.md @@ -12,7 +12,6 @@ A module type. > unit - # Something 1 foo @@ -23,7 +22,6 @@ foo > unit - ## Something 2 --- @@ -34,9 +32,8 @@ foo > unit - foo bar # Something 1-bis -Some text. \ No newline at end of file +Some text. diff --git a/test/generators/markdown/Interlude.md b/test/generators/markdown/Interlude.md index d1f99495f0..03f1df13d4 100644 --- a/test/generators/markdown/Interlude.md +++ b/test/generators/markdown/Interlude.md @@ -12,7 +12,6 @@ Some separate stray text at the top of the module. > unit - Foo. Some stray text that is not associated with any signature item. @@ -27,7 +26,6 @@ A separate block of stray text, adjacent to the preceding one. > unit - Bar. @@ -36,19 +34,16 @@ Bar. > unit - ###### val signature : > unit - ###### val items : > unit - -Stray text at the bottom of the module. \ No newline at end of file +Stray text at the bottom of the module. diff --git a/test/generators/markdown/Labels.A.md b/test/generators/markdown/Labels.A.md index e8377618a1..6e14db519c 100644 --- a/test/generators/markdown/Labels.A.md +++ b/test/generators/markdown/Labels.A.md @@ -4,4 +4,4 @@ A Module `Labels.A` -# Attached to module \ No newline at end of file +# Attached to module diff --git a/test/generators/markdown/Labels.c.md b/test/generators/markdown/Labels.c.md index c47ed42384..b56e12b938 100644 --- a/test/generators/markdown/Labels.c.md +++ b/test/generators/markdown/Labels.c.md @@ -4,4 +4,4 @@ c Class `Labels.c` -# Attached to class \ No newline at end of file +# Attached to class diff --git a/test/generators/markdown/Labels.class-type-cs.md b/test/generators/markdown/Labels.class-type-cs.md index dfa7735e31..e61680835c 100644 --- a/test/generators/markdown/Labels.class-type-cs.md +++ b/test/generators/markdown/Labels.class-type-cs.md @@ -4,4 +4,4 @@ cs Class type `Labels.cs` -# Attached to class type \ No newline at end of file +# Attached to class type diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index 491e6eaa51..29f24c37c4 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -22,7 +22,6 @@ Attached to type > [t](#type-t) - Attached to value @@ -31,7 +30,6 @@ Attached to value > unit -> [t](#type-t) - Attached to external @@ -58,7 +56,6 @@ Attached to exception > .. - ###### type [x](#type-x) += @@ -75,7 +72,6 @@ Attached to extension > [A](Labels.A.md) - Attached to module subst @@ -84,7 +80,6 @@ Attached to module subst > [t](#type-t) - Attached to type subst @@ -112,29 +107,43 @@ Attached to field Testing that labels can be referenced - [Attached to unit](#L1) + - [Attached to nothing](#L2) + - [Attached to module](#L3) + - [Attached to type](#L4) + - [Attached to value](#L5) + - [Attached to module type](#L6) + - [Attached to class](#L7) + - [Attached to class type](#L8) + - [Attached to exception](#L9) + - [Attached to extension](#L10) + - [Attached to module subst](#L11) + - [Attached to type subst](#L12) + - [Attached to constructor](#L13) + -- [Attached to field](#L14) \ No newline at end of file +- [Attached to field](#L14) + diff --git a/test/generators/markdown/Labels.module-type-S.md b/test/generators/markdown/Labels.module-type-S.md index 414dc21d03..8b7baf8aed 100644 --- a/test/generators/markdown/Labels.module-type-S.md +++ b/test/generators/markdown/Labels.module-type-S.md @@ -4,4 +4,4 @@ S Module type `Labels.S` -# Attached to module type \ No newline at end of file +# Attached to module type diff --git a/test/generators/markdown/Markup.X.md b/test/generators/markdown/Markup.X.md index 35c6b00818..455eb86b2d 100644 --- a/test/generators/markdown/Markup.X.md +++ b/test/generators/markdown/Markup.X.md @@ -2,4 +2,4 @@ Markup X -Module `Markup.X` \ No newline at end of file +Module `Markup.X` diff --git a/test/generators/markdown/Markup.Y.md b/test/generators/markdown/Markup.Y.md index 1c3c0d9459..2ee44eaae5 100644 --- a/test/generators/markdown/Markup.Y.md +++ b/test/generators/markdown/Markup.Y.md @@ -2,4 +2,4 @@ Markup Y -Module `Markup.Y` \ No newline at end of file +Module `Markup.Y` diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 9bf7f46367..d47b98a60a 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -73,48 +73,62 @@ let foo = () let bar = ignore foo ``` - There are also verbatim blocks: ``` The main difference is these don't get syntax highlighting. ``` - # Lists - This is a + - shorthand bulleted list, + - and the paragraphs in each list item support _styling_ . + 1. This is a + 2. shorthand numbered list. + - Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break + just creates a paragraph outside the list. - Similarly, inserting a blank line between two list items + - creates two separate lists. + - To get around this limitation, one can use explicitly-delimited lists. + - This one is bulleted, + 1. but there is also the numbered variant. + - - lists + - can be nested + - and can include references + - [`foo`](#val-foo) + + # Unicode @@ -130,7 +144,6 @@ Raw HTML can be as inline elements in element, and won't be wrapped in paragraph tags by the HTML generator. - # Modules @[`X`](Markup.X.md): @@ -171,7 +184,6 @@ Each comment can end with zero or more tags. Here are some examples: > unit - Comments in structure items **support** _markup_ , t o o . Some modules to support references. @@ -182,4 +194,4 @@ Some modules to support references. -###### module [Y](Markup.Y.md) \ No newline at end of file +###### module [Y](Markup.Y.md) diff --git a/test/generators/markdown/Module.M'.md b/test/generators/markdown/Module.M'.md index 2885863222..0a5637bbd0 100644 --- a/test/generators/markdown/Module.M'.md +++ b/test/generators/markdown/Module.M'.md @@ -2,4 +2,4 @@ Module M' -Module `Module.M'` \ No newline at end of file +Module `Module.M'` diff --git a/test/generators/markdown/Module.Mutually.md b/test/generators/markdown/Module.Mutually.md index 2e5696a12c..16688613af 100644 --- a/test/generators/markdown/Module.Mutually.md +++ b/test/generators/markdown/Module.Mutually.md @@ -2,4 +2,4 @@ Module Mutually -Module `Module.Mutually` \ No newline at end of file +Module `Module.Mutually` diff --git a/test/generators/markdown/Module.Recursive.md b/test/generators/markdown/Module.Recursive.md index 74daca47f2..eca3d33962 100644 --- a/test/generators/markdown/Module.Recursive.md +++ b/test/generators/markdown/Module.Recursive.md @@ -2,4 +2,4 @@ Module Recursive -Module `Module.Recursive` \ No newline at end of file +Module `Module.Recursive` diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index 43248bd356..f14ad7d2ae 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -10,7 +10,6 @@ Foo. > unit - The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See [https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701) . @@ -27,7 +26,6 @@ The module needs at least one signature item, otherwise a bug causes the compile > [S](Module.module-type-S.md) - ###### module type [S3](Module.module-type-S3.md) @@ -70,4 +68,4 @@ The module needs at least one signature item, otherwise a bug causes the compile -###### module [Recursive](Module.Recursive.md) \ No newline at end of file +###### module [Recursive](Module.Recursive.md) diff --git a/test/generators/markdown/Module.module-type-S.M.md b/test/generators/markdown/Module.module-type-S.M.md index 55c9c052c6..88a2ff84ed 100644 --- a/test/generators/markdown/Module.module-type-S.M.md +++ b/test/generators/markdown/Module.module-type-S.M.md @@ -4,4 +4,4 @@ S M -Module `S.M` \ No newline at end of file +Module `S.M` diff --git a/test/generators/markdown/Module.module-type-S.md b/test/generators/markdown/Module.module-type-S.md index 7fac8be3c5..bc478c65d0 100644 --- a/test/generators/markdown/Module.module-type-S.md +++ b/test/generators/markdown/Module.module-type-S.md @@ -22,4 +22,4 @@ Module type `Module.S` -###### module [M](Module.module-type-S.M.md) \ No newline at end of file +###### module [M](Module.module-type-S.M.md) diff --git a/test/generators/markdown/Module.module-type-S3.M.md b/test/generators/markdown/Module.module-type-S3.M.md index ca501af660..0a6cfc1dd9 100644 --- a/test/generators/markdown/Module.module-type-S3.M.md +++ b/test/generators/markdown/Module.module-type-S3.M.md @@ -4,4 +4,4 @@ S3 M -Module `S3.M` \ No newline at end of file +Module `S3.M` diff --git a/test/generators/markdown/Module.module-type-S3.md b/test/generators/markdown/Module.module-type-S3.md index e931cf5ed7..30ce278b32 100644 --- a/test/generators/markdown/Module.module-type-S3.md +++ b/test/generators/markdown/Module.module-type-S3.md @@ -10,14 +10,12 @@ Module type `Module.S3` > int - ###### type u = > string - ###### type 'a v @@ -28,4 +26,4 @@ Module type `Module.S3` -###### module [M](Module.module-type-S3.M.md) \ No newline at end of file +###### module [M](Module.module-type-S3.M.md) diff --git a/test/generators/markdown/Module.module-type-S4.M.md b/test/generators/markdown/Module.module-type-S4.M.md index f774eef789..953efa4b1a 100644 --- a/test/generators/markdown/Module.module-type-S4.M.md +++ b/test/generators/markdown/Module.module-type-S4.M.md @@ -4,4 +4,4 @@ S4 M -Module `S4.M` \ No newline at end of file +Module `S4.M` diff --git a/test/generators/markdown/Module.module-type-S4.md b/test/generators/markdown/Module.module-type-S4.md index 57c7e6eede..b9f0f65a85 100644 --- a/test/generators/markdown/Module.module-type-S4.md +++ b/test/generators/markdown/Module.module-type-S4.md @@ -18,4 +18,4 @@ Module type `Module.S4` -###### module [M](Module.module-type-S4.M.md) \ No newline at end of file +###### module [M](Module.module-type-S4.M.md) diff --git a/test/generators/markdown/Module.module-type-S5.M.md b/test/generators/markdown/Module.module-type-S5.M.md index 5f16cdbdfd..e7bc465b04 100644 --- a/test/generators/markdown/Module.module-type-S5.M.md +++ b/test/generators/markdown/Module.module-type-S5.M.md @@ -4,4 +4,4 @@ S5 M -Module `S5.M` \ No newline at end of file +Module `S5.M` diff --git a/test/generators/markdown/Module.module-type-S5.md b/test/generators/markdown/Module.module-type-S5.md index ab0e3ec09f..db79daa617 100644 --- a/test/generators/markdown/Module.module-type-S5.md +++ b/test/generators/markdown/Module.module-type-S5.md @@ -18,4 +18,4 @@ Module type `Module.S5` -###### module [M](Module.module-type-S5.M.md) \ No newline at end of file +###### module [M](Module.module-type-S5.M.md) diff --git a/test/generators/markdown/Module.module-type-S6.M.md b/test/generators/markdown/Module.module-type-S6.M.md index f0283d8cb3..baa9214fd9 100644 --- a/test/generators/markdown/Module.module-type-S6.M.md +++ b/test/generators/markdown/Module.module-type-S6.M.md @@ -4,4 +4,4 @@ S6 M -Module `S6.M` \ No newline at end of file +Module `S6.M` diff --git a/test/generators/markdown/Module.module-type-S6.md b/test/generators/markdown/Module.module-type-S6.md index 9c82d20282..90e6458ae7 100644 --- a/test/generators/markdown/Module.module-type-S6.md +++ b/test/generators/markdown/Module.module-type-S6.md @@ -18,4 +18,4 @@ Module type `Module.S6` -###### module [M](Module.module-type-S6.M.md) \ No newline at end of file +###### module [M](Module.module-type-S6.M.md) diff --git a/test/generators/markdown/Module.module-type-S8.md b/test/generators/markdown/Module.module-type-S8.md index 7bdb906059..e7dcfd351b 100644 --- a/test/generators/markdown/Module.module-type-S8.md +++ b/test/generators/markdown/Module.module-type-S8.md @@ -18,4 +18,4 @@ Module type `Module.S8` -###### type ('a, 'b) w \ No newline at end of file +###### type ('a, 'b) w diff --git a/test/generators/markdown/Module.module-type-S9.md b/test/generators/markdown/Module.module-type-S9.md index 728e55f3e6..a5213a069b 100644 --- a/test/generators/markdown/Module.module-type-S9.md +++ b/test/generators/markdown/Module.module-type-S9.md @@ -2,4 +2,4 @@ Module S9 -Module type `Module.S9` \ No newline at end of file +Module type `Module.S9` diff --git a/test/generators/markdown/Module_type_alias.md b/test/generators/markdown/Module_type_alias.md index 54b1605993..3b87c2acf5 100644 --- a/test/generators/markdown/Module_type_alias.md +++ b/test/generators/markdown/Module_type_alias.md @@ -18,7 +18,6 @@ Module Type Aliases > [A](Module_type_alias.module-type-A.md) - ###### module type [E](Module_type_alias.module-type-E.md) diff --git a/test/generators/markdown/Module_type_alias.module-type-A.md b/test/generators/markdown/Module_type_alias.module-type-A.md index 616a565f1a..6ac3e28d94 100644 --- a/test/generators/markdown/Module_type_alias.module-type-A.md +++ b/test/generators/markdown/Module_type_alias.module-type-A.md @@ -6,4 +6,4 @@ Module type `Module_type_alias.A` -###### type a \ No newline at end of file +###### type a diff --git a/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md b/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md index 7658a529d8..be60e99bfa 100644 --- a/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md +++ b/test/generators/markdown/Module_type_alias.module-type-B.argument-1-C.md @@ -8,4 +8,4 @@ Parameter `B.1-C` -###### type c \ No newline at end of file +###### type c diff --git a/test/generators/markdown/Module_type_alias.module-type-B.md b/test/generators/markdown/Module_type_alias.module-type-B.md index 2bfe7faabf..b875dffb25 100644 --- a/test/generators/markdown/Module_type_alias.module-type-B.md +++ b/test/generators/markdown/Module_type_alias.module-type-B.md @@ -14,4 +14,4 @@ Module type `Module_type_alias.B` -###### type b \ No newline at end of file +###### type b diff --git a/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md b/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md index a32b3fac9c..a442ee344c 100644 --- a/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md +++ b/test/generators/markdown/Module_type_alias.module-type-E.argument-1-F.md @@ -8,4 +8,4 @@ Parameter `E.1-F` -###### type f \ No newline at end of file +###### type f diff --git a/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md b/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md index 73fd867bbc..dce23843d0 100644 --- a/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md +++ b/test/generators/markdown/Module_type_alias.module-type-E.argument-2-C.md @@ -8,4 +8,4 @@ Parameter `E.2-C` -###### type c \ No newline at end of file +###### type c diff --git a/test/generators/markdown/Module_type_alias.module-type-E.md b/test/generators/markdown/Module_type_alias.module-type-E.md index aacddc9031..8e977c3cdd 100644 --- a/test/generators/markdown/Module_type_alias.module-type-E.md +++ b/test/generators/markdown/Module_type_alias.module-type-E.md @@ -18,4 +18,4 @@ Module type `Module_type_alias.E` -###### type b \ No newline at end of file +###### type b diff --git a/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md b/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md index f7f64f136c..f3c717d676 100644 --- a/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md +++ b/test/generators/markdown/Module_type_alias.module-type-G.argument-1-H.md @@ -8,4 +8,4 @@ Parameter `G.1-H` -###### type h \ No newline at end of file +###### type h diff --git a/test/generators/markdown/Module_type_alias.module-type-G.md b/test/generators/markdown/Module_type_alias.module-type-G.md index 6c8aeb4d2d..6aa8f87a10 100644 --- a/test/generators/markdown/Module_type_alias.module-type-G.md +++ b/test/generators/markdown/Module_type_alias.module-type-G.md @@ -14,4 +14,4 @@ Module type `Module_type_alias.G` -###### type a \ No newline at end of file +###### type a diff --git a/test/generators/markdown/Module_type_subst.Basic.md b/test/generators/markdown/Module_type_subst.Basic.md index 092813d26f..933b6873e5 100644 --- a/test/generators/markdown/Module_type_subst.Basic.md +++ b/test/generators/markdown/Module_type_subst.Basic.md @@ -26,4 +26,4 @@ Module `Module_type_subst.Basic` -###### module type [c](Module_type_subst.Basic.module-type-c.md) \ No newline at end of file +###### module type [c](Module_type_subst.Basic.module-type-c.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md index 0ea28f8a5b..a629bc86ed 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.M.md @@ -6,4 +6,4 @@ a M -Module `a.M` \ No newline at end of file +Module `a.M` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-a.md b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md index 73918989a9..9c371ed646 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md @@ -12,7 +12,6 @@ Module type `Basic.a` > [s](Module_type_subst.module-type-s.md) - -###### module [M](Module_type_subst.Basic.module-type-a.M.md) \ No newline at end of file +###### module [M](Module_type_subst.Basic.module-type-a.M.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md index 159056b5d9..a57798d11e 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-c.M.md @@ -6,4 +6,4 @@ c M -Module `c.M` \ No newline at end of file +Module `c.M` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-c.md b/test/generators/markdown/Module_type_subst.Basic.module-type-c.md index bab3b0b873..83d9c0a717 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-c.md @@ -8,4 +8,4 @@ Module type `Basic.c` -###### module [M](Module_type_subst.Basic.module-type-c.M.md) \ No newline at end of file +###### module [M](Module_type_subst.Basic.module-type-c.M.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md index 26a86fb815..361821f17f 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md @@ -8,4 +8,4 @@ Module type `Basic.u` -###### module type [T](Module_type_subst.Basic.module-type-u.module-type-T.md) \ No newline at end of file +###### module type [T](Module_type_subst.Basic.module-type-u.module-type-T.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md index aa83b60587..9763654545 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.module-type-T.md @@ -6,4 +6,4 @@ u T -Module type `u.T` \ No newline at end of file +Module type `u.T` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md index a6ad0b5a60..1f4adbef62 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.M.md @@ -6,4 +6,4 @@ u2 M -Module `u2.M` \ No newline at end of file +Module `u2.M` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md index faf31b6423..8d479a4e08 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md @@ -12,4 +12,4 @@ Module type `Basic.u2` -###### module [M](Module_type_subst.Basic.module-type-u2.M.md) \ No newline at end of file +###### module [M](Module_type_subst.Basic.module-type-u2.M.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md index 40af069288..2534590734 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.module-type-T.md @@ -6,4 +6,4 @@ u2 T -Module type `u2.T` \ No newline at end of file +Module type `u2.T` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md index fba608ead9..dccb75219c 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.M.md @@ -6,4 +6,4 @@ with_2 M -Module `with_2.M` \ No newline at end of file +Module `with_2.M` diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md index 5ce3116017..51476ddab2 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md @@ -12,4 +12,4 @@ Module type `Basic.with_2` -###### module [M](Module_type_subst.Basic.module-type-with_2.M.md) \ No newline at end of file +###### module [M](Module_type_subst.Basic.module-type-with_2.M.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md index 6a99e90bff..35a98ffcfb 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.module-type-T.md @@ -6,4 +6,4 @@ with_2 T -Module type `with_2.T` \ No newline at end of file +Module type `with_2.T` diff --git a/test/generators/markdown/Module_type_subst.Local.md b/test/generators/markdown/Module_type_subst.Local.md index 177bf1ef4e..57fc04908d 100644 --- a/test/generators/markdown/Module_type_subst.Local.md +++ b/test/generators/markdown/Module_type_subst.Local.md @@ -10,7 +10,6 @@ Module `Module_type_subst.Local` > int * int - ###### module type [local](Module_type_subst.Local.module-type-local.md) @@ -21,7 +20,6 @@ Module `Module_type_subst.Local` > [local](Module_type_subst.Local.module-type-local.md) - -###### module type [s](Module_type_subst.Local.module-type-s.md) \ No newline at end of file +###### module type [s](Module_type_subst.Local.module-type-s.md) diff --git a/test/generators/markdown/Module_type_subst.Local.module-type-s.md b/test/generators/markdown/Module_type_subst.Local.module-type-s.md index 1b0d16738b..7778d7a6d6 100644 --- a/test/generators/markdown/Module_type_subst.Local.module-type-s.md +++ b/test/generators/markdown/Module_type_subst.Local.module-type-s.md @@ -4,4 +4,4 @@ Local s -Module type `Local.s` \ No newline at end of file +Module type `Local.s` diff --git a/test/generators/markdown/Module_type_subst.Nested.md b/test/generators/markdown/Module_type_subst.Nested.md index d23cc8c13f..ff38ef9b26 100644 --- a/test/generators/markdown/Module_type_subst.Nested.md +++ b/test/generators/markdown/Module_type_subst.Nested.md @@ -14,4 +14,4 @@ Module `Module_type_subst.Nested` -###### module type [with_subst](Module_type_subst.Nested.module-type-with_subst.md) \ No newline at end of file +###### module type [with_subst](Module_type_subst.Nested.module-type-with_subst.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md index 12de1c48d0..fd24516325 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md @@ -10,4 +10,4 @@ Module `nested.N` -###### module type [t](Module_type_subst.Nested.module-type-nested.N.module-type-t.md) \ No newline at end of file +###### module type [t](Module_type_subst.Nested.module-type-nested.N.module-type-t.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md index d84158036a..154cdf7725 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.module-type-t.md @@ -8,4 +8,4 @@ N t -Module type `N.t` \ No newline at end of file +Module type `N.t` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md index a09a44ef2e..b6929a6605 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.md @@ -8,4 +8,4 @@ Module type `Nested.nested` -###### module [N](Module_type_subst.Nested.module-type-nested.N.md) \ No newline at end of file +###### module [N](Module_type_subst.Nested.module-type-nested.N.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md index 04a206a65b..d83636da0e 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_.md @@ -8,4 +8,4 @@ Module type `Nested.with_` -###### module [N](Module_type_subst.Nested.module-type-with_.N.md) \ No newline at end of file +###### module [N](Module_type_subst.Nested.module-type-with_.N.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md index 20a4a766c9..59a3b82f42 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.N.md @@ -6,4 +6,4 @@ with_subst N -Module `with_subst.N` \ No newline at end of file +Module `with_subst.N` diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md index 6e26782142..9e976d74bd 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-with_subst.md @@ -8,4 +8,4 @@ Module type `Nested.with_subst` -###### module [N](Module_type_subst.Nested.module-type-with_subst.N.md) \ No newline at end of file +###### module [N](Module_type_subst.Nested.module-type-with_subst.N.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.md b/test/generators/markdown/Module_type_subst.Structural.md index ece362070a..61d75d9812 100644 --- a/test/generators/markdown/Module_type_subst.Structural.md +++ b/test/generators/markdown/Module_type_subst.Structural.md @@ -10,4 +10,4 @@ Module `Module_type_subst.Structural` -###### module type [w](Module_type_subst.Structural.module-type-w.md) \ No newline at end of file +###### module type [w](Module_type_subst.Structural.module-type-w.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md index a3758f71a1..7280e0bd6e 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md @@ -8,4 +8,4 @@ Module type `Structural.u` -###### module type [a](Module_type_subst.Structural.module-type-u.module-type-a.md) \ No newline at end of file +###### module type [a](Module_type_subst.Structural.module-type-u.module-type-a.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md index 3fe7ebbe2a..881b38b441 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md @@ -10,4 +10,4 @@ Module type `u.a` -###### module type [b](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md) \ No newline at end of file +###### module type [b](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md index 2f5d401940..fa75996b71 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md @@ -12,4 +12,4 @@ Module type `a.b` -###### module type [c](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md) \ No newline at end of file +###### module type [c](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md index 516a3d6020..55fc295c8f 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md @@ -18,4 +18,4 @@ Module type `b.c` -######    | A of [t](#type-t) \ No newline at end of file +######    | A of [t](#type-t) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md index 6cb288647c..558ef4c443 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md @@ -8,4 +8,4 @@ Module type `Structural.w` -###### module type [a](Module_type_subst.Structural.module-type-w.module-type-a.md) \ No newline at end of file +###### module type [a](Module_type_subst.Structural.module-type-w.module-type-a.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md index 8340939ff5..48d151f86b 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md @@ -10,4 +10,4 @@ Module type `w.a` -###### module type [b](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md) \ No newline at end of file +###### module type [b](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md index ad16ec0e5a..770b469358 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md @@ -12,4 +12,4 @@ Module type `a.b` -###### module type [c](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md) \ No newline at end of file +###### module type [c](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md index d6687ef073..a66176d05d 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md @@ -18,4 +18,4 @@ Module type `b.c` -######    | A of [t](#type-t) \ No newline at end of file +######    | A of [t](#type-t) diff --git a/test/generators/markdown/Module_type_subst.md b/test/generators/markdown/Module_type_subst.md index 01a5d2ccdf..ba92f01294 100644 --- a/test/generators/markdown/Module_type_subst.md +++ b/test/generators/markdown/Module_type_subst.md @@ -20,4 +20,4 @@ Module `Module_type_subst` -###### module [Structural](Module_type_subst.Structural.md) \ No newline at end of file +###### module [Structural](Module_type_subst.Structural.md) diff --git a/test/generators/markdown/Module_type_subst.module-type-s.md b/test/generators/markdown/Module_type_subst.module-type-s.md index 874df212cc..f17741e580 100644 --- a/test/generators/markdown/Module_type_subst.module-type-s.md +++ b/test/generators/markdown/Module_type_subst.module-type-s.md @@ -2,4 +2,4 @@ Module_type_subst s -Module type `Module_type_subst.s` \ No newline at end of file +Module type `Module_type_subst.s` diff --git a/test/generators/markdown/Nested.F.argument-1-Arg1.md b/test/generators/markdown/Nested.F.argument-1-Arg1.md index f645466571..0eafa35ad3 100644 --- a/test/generators/markdown/Nested.F.argument-1-Arg1.md +++ b/test/generators/markdown/Nested.F.argument-1-Arg1.md @@ -22,5 +22,4 @@ Some type. > [t](#type-t) - -The value of y. \ No newline at end of file +The value of y. diff --git a/test/generators/markdown/Nested.F.argument-2-Arg2.md b/test/generators/markdown/Nested.F.argument-2-Arg2.md index 71f423a5a2..c4e567dfa1 100644 --- a/test/generators/markdown/Nested.F.argument-2-Arg2.md +++ b/test/generators/markdown/Nested.F.argument-2-Arg2.md @@ -12,4 +12,4 @@ Parameter `F.2-Arg2` ###### type t -Some type. \ No newline at end of file +Some type. diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md index f47b5f8f95..9fbdebcd09 100644 --- a/test/generators/markdown/Nested.F.md +++ b/test/generators/markdown/Nested.F.md @@ -28,5 +28,4 @@ Some additional comments. > [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) - -Some type. \ No newline at end of file +Some type. diff --git a/test/generators/markdown/Nested.X.md b/test/generators/markdown/Nested.X.md index cb5d138815..d87c983f29 100644 --- a/test/generators/markdown/Nested.X.md +++ b/test/generators/markdown/Nested.X.md @@ -24,5 +24,4 @@ Some type. > [t](#type-t) - -The value of x. \ No newline at end of file +The value of x. diff --git a/test/generators/markdown/Nested.inherits.md b/test/generators/markdown/Nested.inherits.md index 4101a530cb..53c10a54c6 100644 --- a/test/generators/markdown/Nested.inherits.md +++ b/test/generators/markdown/Nested.inherits.md @@ -6,4 +6,4 @@ Class `Nested.inherits` -###### inherit [z](Nested.z.md) \ No newline at end of file +###### inherit [z](Nested.z.md) diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md index 17be89ce16..a42a9b76bf 100644 --- a/test/generators/markdown/Nested.md +++ b/test/generators/markdown/Nested.md @@ -38,4 +38,4 @@ This is class z. -###### class virtual [inherits](Nested.inherits.md) \ No newline at end of file +###### class virtual [inherits](Nested.inherits.md) diff --git a/test/generators/markdown/Nested.module-type-Y.md b/test/generators/markdown/Nested.module-type-Y.md index 6e494e2ff9..cf2b911e73 100644 --- a/test/generators/markdown/Nested.module-type-Y.md +++ b/test/generators/markdown/Nested.module-type-Y.md @@ -24,5 +24,4 @@ Some type. > [t](#type-t) - -The value of y. \ No newline at end of file +The value of y. diff --git a/test/generators/markdown/Nested.z.md b/test/generators/markdown/Nested.z.md index 9dd6f1871f..0d28a8d38e 100644 --- a/test/generators/markdown/Nested.z.md +++ b/test/generators/markdown/Nested.z.md @@ -14,7 +14,6 @@ Some additional comments. > int - Some value. @@ -23,7 +22,6 @@ Some value. > int - # Methods @@ -32,7 +30,6 @@ Some value. > int - Some method. diff --git a/test/generators/markdown/Ocamlary.Aliases.Foo.md b/test/generators/markdown/Ocamlary.Aliases.Foo.md index eb08b56ee0..d141c490ab 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Foo.md +++ b/test/generators/markdown/Ocamlary.Aliases.Foo.md @@ -24,4 +24,4 @@ Module `Aliases.Foo` -###### module [E](Ocamlary.Aliases.Foo.E.md) \ No newline at end of file +###### module [E](Ocamlary.Aliases.Foo.E.md) diff --git a/test/generators/markdown/Ocamlary.Aliases.P1.md b/test/generators/markdown/Ocamlary.Aliases.P1.md index c1de46c7b7..79abe97e96 100644 --- a/test/generators/markdown/Ocamlary.Aliases.P1.md +++ b/test/generators/markdown/Ocamlary.Aliases.P1.md @@ -8,4 +8,4 @@ Module `Aliases.P1` -###### module [Y](Ocamlary.Aliases.P1.Y.md) \ No newline at end of file +###### module [Y](Ocamlary.Aliases.P1.Y.md) diff --git a/test/generators/markdown/Ocamlary.Aliases.Std.md b/test/generators/markdown/Ocamlary.Aliases.Std.md index c848f095da..caf8037354 100644 --- a/test/generators/markdown/Ocamlary.Aliases.Std.md +++ b/test/generators/markdown/Ocamlary.Aliases.Std.md @@ -12,28 +12,24 @@ Module `Aliases.Std` > [Foo.A](Ocamlary.Aliases.Foo.A.md) - ###### module B = > [Foo.B](Ocamlary.Aliases.Foo.B.md) - ###### module C = > [Foo.C](Ocamlary.Aliases.Foo.C.md) - ###### module D = > [Foo.D](Ocamlary.Aliases.Foo.D.md) - ###### module E = diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index 23365f4b08..d22d259ac9 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -16,21 +16,18 @@ Let's imitate jst's layout. > [Foo.A](Ocamlary.Aliases.Foo.A.md) - ###### type tata = > [Foo.A.t](Ocamlary.Aliases.Foo.A.md#type-t) - ###### type tbtb = > [Foo.B.t](Ocamlary.Aliases.Foo.B.md#type-t) - ###### type tete @@ -41,14 +38,12 @@ Let's imitate jst's layout. > [A'.t](Ocamlary.Aliases.Foo.A.md#type-t) - ###### type tete2 = > [Foo.E.t](Ocamlary.Aliases.Foo.E.md#type-t) - ###### module [Std](Ocamlary.Aliases.Std.md) @@ -59,7 +54,6 @@ Let's imitate jst's layout. > [Std.E.t](Ocamlary.Aliases.Foo.E.md#type-t) - ### include of Foo --- @@ -72,28 +66,24 @@ Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases > [Foo.A](Ocamlary.Aliases.Foo.A.md) - ###### module B = > [Foo.B](Ocamlary.Aliases.Foo.B.md) - ###### module C = > [Foo.C](Ocamlary.Aliases.Foo.C.md) - ###### module D = > [Foo.D](Ocamlary.Aliases.Foo.D.md) - ###### module [E](Ocamlary.Aliases.E.md) @@ -104,7 +94,6 @@ Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases > [A.t](Ocamlary.Aliases.Foo.A.md#type-t) - And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and [`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) @@ -121,21 +110,18 @@ And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and [`Foo.B.i > [P2.Z](Ocamlary.Aliases.P1.Y.md) - ###### module X2 = > [P2.Z](Ocamlary.Aliases.P1.Y.md) - ###### type p1 = > [X1.t](Ocamlary.Aliases.P1.Y.md#type-t) - ###### type p2 = diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md index 9a892d9e89..7456d001b1 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md @@ -8,4 +8,4 @@ Module `CanonicalTest.Base` -###### module [List](Ocamlary.CanonicalTest.Base.List.md) \ No newline at end of file +###### module [List](Ocamlary.CanonicalTest.Base.List.md) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md index e6dbd2dc8f..4af17993a5 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md @@ -16,21 +16,18 @@ Module `CanonicalTest.Base_Tests` > [Base.List](Ocamlary.CanonicalTest.Base.List.md) - ###### val foo : > int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) - ###### val bar : > 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) - ###### val baz : diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md index 54b237ef50..5199edd9c9 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md @@ -12,7 +12,6 @@ Module `CanonicalTest.List_modif` > 'c [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) - ###### val id : diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.md b/test/generators/markdown/Ocamlary.CanonicalTest.md index de4edcfe70..0d9f10b75e 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.md @@ -14,4 +14,4 @@ Module `Ocamlary.CanonicalTest` -###### module [List_modif](Ocamlary.CanonicalTest.List_modif.md) \ No newline at end of file +###### module [List_modif](Ocamlary.CanonicalTest.List_modif.md) diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md index 875f6f6728..f0bea03d81 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index 6405679355..b3197ff26b 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -14,7 +14,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.CollectionModule.md#type-collection) - This comment is for `t` . @@ -27,4 +26,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index 9ed0055792..7702b11b16 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md index 0355a783a5..1b97174584 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.md @@ -28,5 +28,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.md index 7410030cdb..af01294c8d 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md @@ -10,4 +10,4 @@ Module `X.Y` -###### class [c](Ocamlary.Dep1.X.Y.c.md) \ No newline at end of file +###### class [c](Ocamlary.Dep1.X.Y.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep1.X.md b/test/generators/markdown/Ocamlary.Dep1.X.md index 73d8eb8d32..dcc14a1bcb 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.md @@ -8,4 +8,4 @@ Module `Dep1.X` -###### module [Y](Ocamlary.Dep1.X.Y.md) \ No newline at end of file +###### module [Y](Ocamlary.Dep1.X.Y.md) diff --git a/test/generators/markdown/Ocamlary.Dep1.md b/test/generators/markdown/Ocamlary.Dep1.md index b10cb0e737..cf4efa4931 100644 --- a/test/generators/markdown/Ocamlary.Dep1.md +++ b/test/generators/markdown/Ocamlary.Dep1.md @@ -10,4 +10,4 @@ Module `Ocamlary.Dep1` -###### module [X](Ocamlary.Dep1.X.md) \ No newline at end of file +###### module [X](Ocamlary.Dep1.X.md) diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md index 10894be264..c476643fe3 100644 --- a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep1.S` -###### class [c](Ocamlary.Dep1.module-type-S.c.md) \ No newline at end of file +###### class [c](Ocamlary.Dep1.module-type-S.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep11.md b/test/generators/markdown/Ocamlary.Dep11.md index 64aab282b7..8a3e164b27 100644 --- a/test/generators/markdown/Ocamlary.Dep11.md +++ b/test/generators/markdown/Ocamlary.Dep11.md @@ -6,4 +6,4 @@ Module `Ocamlary.Dep11` -###### module type [S](Ocamlary.Dep11.module-type-S.md) \ No newline at end of file +###### module type [S](Ocamlary.Dep11.module-type-S.md) diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md index 9e7d57161b..4bfd93a3c3 100644 --- a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep11.S` -###### class [c](Ocamlary.Dep11.module-type-S.c.md) \ No newline at end of file +###### class [c](Ocamlary.Dep11.module-type-S.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md index 100b34a796..8c838e5638 100644 --- a/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md @@ -8,4 +8,4 @@ Parameter `Dep12.1-Arg` -###### module type S \ No newline at end of file +###### module type S diff --git a/test/generators/markdown/Ocamlary.Dep13.md b/test/generators/markdown/Ocamlary.Dep13.md index 6a9d1cb8f7..9aae84433f 100644 --- a/test/generators/markdown/Ocamlary.Dep13.md +++ b/test/generators/markdown/Ocamlary.Dep13.md @@ -6,4 +6,4 @@ Module `Ocamlary.Dep13` -###### class [c](Ocamlary.Dep13.c.md) \ No newline at end of file +###### class [c](Ocamlary.Dep13.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md index 3ad389d8d8..2a7ebe9516 100644 --- a/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md @@ -12,4 +12,4 @@ Parameter `Dep2.1-Arg` -###### module [X](Ocamlary.Dep2.argument-1-Arg.X.md) \ No newline at end of file +###### module [X](Ocamlary.Dep2.argument-1-Arg.X.md) diff --git a/test/generators/markdown/Ocamlary.Dep3.md b/test/generators/markdown/Ocamlary.Dep3.md index fd9c860f9b..0aebd3078e 100644 --- a/test/generators/markdown/Ocamlary.Dep3.md +++ b/test/generators/markdown/Ocamlary.Dep3.md @@ -6,4 +6,4 @@ Module `Ocamlary.Dep3` -###### type a \ No newline at end of file +###### type a diff --git a/test/generators/markdown/Ocamlary.Dep4.X.md b/test/generators/markdown/Ocamlary.Dep4.X.md index f95cbafc40..559eef0435 100644 --- a/test/generators/markdown/Ocamlary.Dep4.X.md +++ b/test/generators/markdown/Ocamlary.Dep4.X.md @@ -8,4 +8,4 @@ Module `Dep4.X` -###### type b \ No newline at end of file +###### type b diff --git a/test/generators/markdown/Ocamlary.Dep4.md b/test/generators/markdown/Ocamlary.Dep4.md index 8f82a81314..8d5a79e7a3 100644 --- a/test/generators/markdown/Ocamlary.Dep4.md +++ b/test/generators/markdown/Ocamlary.Dep4.md @@ -14,4 +14,4 @@ Module `Ocamlary.Dep4` -###### module [X](Ocamlary.Dep4.X.md) \ No newline at end of file +###### module [X](Ocamlary.Dep4.X.md) diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md index a778fb7dfe..692ecaffe5 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md @@ -10,4 +10,4 @@ Module `S.X` -###### type b \ No newline at end of file +###### type b diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md index 843925a23d..8d2b5f5c5e 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md @@ -6,4 +6,4 @@ S Y -Module `S.Y` \ No newline at end of file +Module `S.Y` diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-S.md b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md index 75f4802ab0..3b30c5c8de 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md @@ -12,4 +12,4 @@ Module type `Dep4.S` -###### module [Y](Ocamlary.Dep4.module-type-S.Y.md) \ No newline at end of file +###### module [Y](Ocamlary.Dep4.module-type-S.Y.md) diff --git a/test/generators/markdown/Ocamlary.Dep4.module-type-T.md b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md index a7250f0401..cde7880c43 100644 --- a/test/generators/markdown/Ocamlary.Dep4.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md @@ -8,4 +8,4 @@ Module type `Dep4.T` -###### type b \ No newline at end of file +###### type b diff --git a/test/generators/markdown/Ocamlary.Dep5.Z.md b/test/generators/markdown/Ocamlary.Dep5.Z.md index b08bcf3164..2250570ca5 100644 --- a/test/generators/markdown/Ocamlary.Dep5.Z.md +++ b/test/generators/markdown/Ocamlary.Dep5.Z.md @@ -12,7 +12,6 @@ Module `Dep5.Z` > [Arg.T](Ocamlary.Dep5.argument-1-Arg.md#module-type-T) - ###### module Y = diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md index 62343408d0..b8b09c001f 100644 --- a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md @@ -8,4 +8,4 @@ S Y -Module `S.Y` \ No newline at end of file +Module `S.Y` diff --git a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md index 4635dcf4dd..164768022e 100644 --- a/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md @@ -14,7 +14,6 @@ Module type `1-Arg.S` > [T](Ocamlary.Dep5.argument-1-Arg.md#module-type-T) - -###### module [Y](Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md) \ No newline at end of file +###### module [Y](Ocamlary.Dep5.argument-1-Arg.module-type-S.Y.md) diff --git a/test/generators/markdown/Ocamlary.Dep5.md b/test/generators/markdown/Ocamlary.Dep5.md index f5e3b09afc..eaad110453 100644 --- a/test/generators/markdown/Ocamlary.Dep5.md +++ b/test/generators/markdown/Ocamlary.Dep5.md @@ -14,4 +14,4 @@ Module `Ocamlary.Dep5` -###### module [Z](Ocamlary.Dep5.Z.md) \ No newline at end of file +###### module [Z](Ocamlary.Dep5.Z.md) diff --git a/test/generators/markdown/Ocamlary.Dep6.X.Y.md b/test/generators/markdown/Ocamlary.Dep6.X.Y.md index 910317d232..183fdb76ed 100644 --- a/test/generators/markdown/Ocamlary.Dep6.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep6.X.Y.md @@ -10,4 +10,4 @@ Module `X.Y` -###### type d \ No newline at end of file +###### type d diff --git a/test/generators/markdown/Ocamlary.Dep6.X.md b/test/generators/markdown/Ocamlary.Dep6.X.md index c0f2ab0ad2..3c497b1431 100644 --- a/test/generators/markdown/Ocamlary.Dep6.X.md +++ b/test/generators/markdown/Ocamlary.Dep6.X.md @@ -12,7 +12,6 @@ Module `Dep6.X` > [S](Ocamlary.Dep6.module-type-S.md) - -###### module [Y](Ocamlary.Dep6.X.Y.md) \ No newline at end of file +###### module [Y](Ocamlary.Dep6.X.Y.md) diff --git a/test/generators/markdown/Ocamlary.Dep6.md b/test/generators/markdown/Ocamlary.Dep6.md index 6cb8c97389..43a79833e3 100644 --- a/test/generators/markdown/Ocamlary.Dep6.md +++ b/test/generators/markdown/Ocamlary.Dep6.md @@ -14,4 +14,4 @@ Module `Ocamlary.Dep6` -###### module [X](Ocamlary.Dep6.X.md) \ No newline at end of file +###### module [X](Ocamlary.Dep6.X.md) diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-S.md b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md index a355f2ebde..bc34e6fcbf 100644 --- a/test/generators/markdown/Ocamlary.Dep6.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep6.S` -###### type d \ No newline at end of file +###### type d diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md index d92b4bff39..c1214b411c 100644 --- a/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md @@ -10,4 +10,4 @@ Module `T.Y` -###### type d \ No newline at end of file +###### type d diff --git a/test/generators/markdown/Ocamlary.Dep6.module-type-T.md b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md index 868c99b550..c9e3427cba 100644 --- a/test/generators/markdown/Ocamlary.Dep6.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md @@ -12,7 +12,6 @@ Module type `Dep6.T` > [S](Ocamlary.Dep6.module-type-S.md) - -###### module [Y](Ocamlary.Dep6.module-type-T.Y.md) \ No newline at end of file +###### module [Y](Ocamlary.Dep6.module-type-T.Y.md) diff --git a/test/generators/markdown/Ocamlary.Dep7.M.md b/test/generators/markdown/Ocamlary.Dep7.M.md index d4e1b37396..34eaced164 100644 --- a/test/generators/markdown/Ocamlary.Dep7.M.md +++ b/test/generators/markdown/Ocamlary.Dep7.M.md @@ -12,7 +12,6 @@ Module `Dep7.M` > [Arg.S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) - ###### module Y : diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md index 21de9aec43..3f71a9a7f9 100644 --- a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md @@ -14,7 +14,6 @@ Module `1-Arg.X` > [S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) - ###### module Y : diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md index ebe3ce17ab..684a0fd5a7 100644 --- a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md @@ -16,4 +16,4 @@ Parameter `Dep7.1-Arg` -###### module [X](Ocamlary.Dep7.argument-1-Arg.X.md) \ No newline at end of file +###### module [X](Ocamlary.Dep7.argument-1-Arg.X.md) diff --git a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md index 8f5c1b5f5b..bc3af25b2f 100644 --- a/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md @@ -14,7 +14,6 @@ Module type `1-Arg.T` > [S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S) - ###### module Y : diff --git a/test/generators/markdown/Ocamlary.Dep7.md b/test/generators/markdown/Ocamlary.Dep7.md index 12ed805ed2..284da5267b 100644 --- a/test/generators/markdown/Ocamlary.Dep7.md +++ b/test/generators/markdown/Ocamlary.Dep7.md @@ -14,4 +14,4 @@ Module `Ocamlary.Dep7` -###### module [M](Ocamlary.Dep7.M.md) \ No newline at end of file +###### module [M](Ocamlary.Dep7.M.md) diff --git a/test/generators/markdown/Ocamlary.Dep8.md b/test/generators/markdown/Ocamlary.Dep8.md index bc16e30e6d..e672846442 100644 --- a/test/generators/markdown/Ocamlary.Dep8.md +++ b/test/generators/markdown/Ocamlary.Dep8.md @@ -6,4 +6,4 @@ Module `Ocamlary.Dep8` -###### module type [T](Ocamlary.Dep8.module-type-T.md) \ No newline at end of file +###### module type [T](Ocamlary.Dep8.module-type-T.md) diff --git a/test/generators/markdown/Ocamlary.Dep8.module-type-T.md b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md index b0503be7fd..98d6f2b8a6 100644 --- a/test/generators/markdown/Ocamlary.Dep8.module-type-T.md +++ b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md @@ -8,4 +8,4 @@ Module type `Dep8.T` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md index db8de153b8..e4bfd93347 100644 --- a/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md +++ b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md @@ -8,4 +8,4 @@ Parameter `Dep9.1-X` -###### module type T \ No newline at end of file +###### module type T diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md index 18b37a76a2..a22361ec3f 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md @@ -8,4 +8,4 @@ Module `DoubleInclude1.DoubleInclude2` -###### type double_include \ No newline at end of file +###### type double_include diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.md b/test/generators/markdown/Ocamlary.DoubleInclude1.md index 1775e53383..bb36a9977f 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude1.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude1.md @@ -6,4 +6,4 @@ Module `Ocamlary.DoubleInclude1` -###### module [DoubleInclude2](Ocamlary.DoubleInclude1.DoubleInclude2.md) \ No newline at end of file +###### module [DoubleInclude2](Ocamlary.DoubleInclude1.DoubleInclude2.md) diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md index f32c869e85..b5d0e88132 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md @@ -8,4 +8,4 @@ Module `DoubleInclude3.DoubleInclude2` -###### type double_include \ No newline at end of file +###### type double_include diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.md b/test/generators/markdown/Ocamlary.DoubleInclude3.md index dbfffbf149..09b2b4ce38 100644 --- a/test/generators/markdown/Ocamlary.DoubleInclude3.md +++ b/test/generators/markdown/Ocamlary.DoubleInclude3.md @@ -6,4 +6,4 @@ Module `Ocamlary.DoubleInclude3` -###### module [DoubleInclude2](Ocamlary.DoubleInclude3.DoubleInclude2.md) \ No newline at end of file +###### module [DoubleInclude2](Ocamlary.DoubleInclude3.DoubleInclude2.md) diff --git a/test/generators/markdown/Ocamlary.Empty.md b/test/generators/markdown/Ocamlary.Empty.md index 8a1672f5c7..f7412fe119 100644 --- a/test/generators/markdown/Ocamlary.Empty.md +++ b/test/generators/markdown/Ocamlary.Empty.md @@ -6,4 +6,4 @@ Module `Ocamlary.Empty` A plain, empty module -This module has a signature without any members. \ No newline at end of file +This module has a signature without any members. diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md index 8bc2180e52..843b94f8fb 100644 --- a/test/generators/markdown/Ocamlary.ExtMod.md +++ b/test/generators/markdown/Ocamlary.ExtMod.md @@ -10,11 +10,10 @@ Module `Ocamlary.ExtMod` > .. - ###### type [t](#type-t) += -######    | Leisureforce \ No newline at end of file +######    | Leisureforce diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md index 316e22ab77..9d143cf4eb 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md index 9be53e43d9..d23ba70ece 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -16,7 +16,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) - This comment is for `t` . @@ -29,4 +28,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md index 2e8df6dbae..0c967c70dc 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md index 8972e2f817..35a1197951 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md index 92c93cb63e..0e9582178f 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md @@ -20,5 +20,4 @@ This comment is for `FunctorTypeOf` . > [Collection.collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md index 3f40d2cd27..2437c64596 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md @@ -4,4 +4,4 @@ IncludeInclude1 IncludeInclude2_M -Module `IncludeInclude1.IncludeInclude2_M` \ No newline at end of file +Module `IncludeInclude1.IncludeInclude2_M` diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md index f302249027..a9ce8a56b0 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -10,4 +10,4 @@ Module `Ocamlary.IncludeInclude1` -###### module [IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) \ No newline at end of file +###### module [IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md index 0591c40d25..9cdc665566 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md @@ -8,4 +8,4 @@ Module type `IncludeInclude1.IncludeInclude2` -###### type include_include \ No newline at end of file +###### type include_include diff --git a/test/generators/markdown/Ocamlary.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md index 803d19b7eb..c0b22296e7 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude2_M.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md @@ -2,4 +2,4 @@ Ocamlary IncludeInclude2_M -Module `Ocamlary.IncludeInclude2_M` \ No newline at end of file +Module `Ocamlary.IncludeInclude2_M` diff --git a/test/generators/markdown/Ocamlary.IncludedA.md b/test/generators/markdown/Ocamlary.IncludedA.md index 5fe2f42c9f..d64a057d18 100644 --- a/test/generators/markdown/Ocamlary.IncludedA.md +++ b/test/generators/markdown/Ocamlary.IncludedA.md @@ -6,4 +6,4 @@ Module `Ocamlary.IncludedA` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.M.md b/test/generators/markdown/Ocamlary.M.md index 2a892a6028..067896f835 100644 --- a/test/generators/markdown/Ocamlary.M.md +++ b/test/generators/markdown/Ocamlary.M.md @@ -6,4 +6,4 @@ Module `Ocamlary.M` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md index e36fcb80c3..564f1a2254 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignature.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md @@ -4,4 +4,4 @@ ModuleWithSignature Module `Ocamlary.ModuleWithSignature` -A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) \ No newline at end of file +A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md index ebd0fee282..3cb01089e8 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md @@ -6,4 +6,4 @@ Module `Ocamlary.ModuleWithSignatureAlias` A plain module with an alias signature -@deprecated: \ No newline at end of file +@deprecated: diff --git a/test/generators/markdown/Ocamlary.One.md b/test/generators/markdown/Ocamlary.One.md index 0d8f1cace6..5cf477779f 100644 --- a/test/generators/markdown/Ocamlary.One.md +++ b/test/generators/markdown/Ocamlary.One.md @@ -6,4 +6,4 @@ Module `Ocamlary.One` -###### type one \ No newline at end of file +###### type one diff --git a/test/generators/markdown/Ocamlary.Only_a_module.md b/test/generators/markdown/Ocamlary.Only_a_module.md index fa68b44672..074814befd 100644 --- a/test/generators/markdown/Ocamlary.Only_a_module.md +++ b/test/generators/markdown/Ocamlary.Only_a_module.md @@ -6,4 +6,4 @@ Module `Ocamlary.Only_a_module` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md index debd9211e9..b27baa577d 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index 339dcbb6e8..0a488d62e1 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -14,7 +14,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.Recollection.md#type-collection) - This comment is for `t` . @@ -27,4 +26,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md index 7dd25e3085..7b4b4d096c 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md index 74bc89361a..c92e5cf3a9 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md index 0e67e634fb..d2018b6010 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -16,7 +16,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.Recollection.argument-1-C.md#type-collection) - This comment is for `t` . @@ -29,4 +28,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md index 93055cef64..a118953128 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md index 543258b17a..c9c28d4e82 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md index a2c77f97b1..60301a1d57 100644 --- a/test/generators/markdown/Ocamlary.Recollection.md +++ b/test/generators/markdown/Ocamlary.Recollection.md @@ -20,7 +20,6 @@ This comment is for `CollectionModule` . > [C.element](Ocamlary.Recollection.argument-1-C.md#type-element) list - This comment is for `collection` . @@ -29,7 +28,6 @@ This comment is for `collection` . > [C.collection](Ocamlary.Recollection.argument-1-C.md#type-collection) - ###### module [InnerModuleA](Ocamlary.Recollection.InnerModuleA.md) @@ -42,5 +40,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.With10.md b/test/generators/markdown/Ocamlary.With10.md index 1f89876e0a..3f86b1c480 100644 --- a/test/generators/markdown/Ocamlary.With10.md +++ b/test/generators/markdown/Ocamlary.With10.md @@ -8,4 +8,4 @@ Module `Ocamlary.With10` ###### module type [T](Ocamlary.With10.module-type-T.md) -[`With10.T`](Ocamlary.With10.module-type-T.md) is a submodule type. \ No newline at end of file +[`With10.T`](Ocamlary.With10.module-type-T.md) is a submodule type. diff --git a/test/generators/markdown/Ocamlary.With10.module-type-T.M.md b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md index c87488c24c..f389aa16fe 100644 --- a/test/generators/markdown/Ocamlary.With10.module-type-T.M.md +++ b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md @@ -10,4 +10,4 @@ Module `T.M` -###### module type S \ No newline at end of file +###### module type S diff --git a/test/generators/markdown/Ocamlary.With2.md b/test/generators/markdown/Ocamlary.With2.md index 7ab42eda63..6c5793f6e5 100644 --- a/test/generators/markdown/Ocamlary.With2.md +++ b/test/generators/markdown/Ocamlary.With2.md @@ -6,4 +6,4 @@ Module `Ocamlary.With2` -###### module type [S](Ocamlary.With2.module-type-S.md) \ No newline at end of file +###### module type [S](Ocamlary.With2.module-type-S.md) diff --git a/test/generators/markdown/Ocamlary.With2.module-type-S.md b/test/generators/markdown/Ocamlary.With2.module-type-S.md index 4b8308c52d..993ed60de2 100644 --- a/test/generators/markdown/Ocamlary.With2.module-type-S.md +++ b/test/generators/markdown/Ocamlary.With2.module-type-S.md @@ -8,4 +8,4 @@ Module type `With2.S` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.With3.N.md b/test/generators/markdown/Ocamlary.With3.N.md index d79b2635bb..979c579e4c 100644 --- a/test/generators/markdown/Ocamlary.With3.N.md +++ b/test/generators/markdown/Ocamlary.With3.N.md @@ -8,4 +8,4 @@ Module `With3.N` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.With3.md b/test/generators/markdown/Ocamlary.With3.md index 26c0d7d0a5..f5c82fa793 100644 --- a/test/generators/markdown/Ocamlary.With3.md +++ b/test/generators/markdown/Ocamlary.With3.md @@ -10,7 +10,6 @@ Module `Ocamlary.With3` > [With2](Ocamlary.With2.md) - -###### module [N](Ocamlary.With3.N.md) \ No newline at end of file +###### module [N](Ocamlary.With3.N.md) diff --git a/test/generators/markdown/Ocamlary.With4.N.md b/test/generators/markdown/Ocamlary.With4.N.md index ff57122e36..9c9d6f0966 100644 --- a/test/generators/markdown/Ocamlary.With4.N.md +++ b/test/generators/markdown/Ocamlary.With4.N.md @@ -8,4 +8,4 @@ Module `With4.N` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.With4.md b/test/generators/markdown/Ocamlary.With4.md index e33f59c2e5..bd7b6adc08 100644 --- a/test/generators/markdown/Ocamlary.With4.md +++ b/test/generators/markdown/Ocamlary.With4.md @@ -6,4 +6,4 @@ Module `Ocamlary.With4` -###### module [N](Ocamlary.With4.N.md) \ No newline at end of file +###### module [N](Ocamlary.With4.N.md) diff --git a/test/generators/markdown/Ocamlary.With5.N.md b/test/generators/markdown/Ocamlary.With5.N.md index 500f8022ae..8a28e50377 100644 --- a/test/generators/markdown/Ocamlary.With5.N.md +++ b/test/generators/markdown/Ocamlary.With5.N.md @@ -8,4 +8,4 @@ Module `With5.N` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.With5.md b/test/generators/markdown/Ocamlary.With5.md index 8f95d99cbd..137341d6df 100644 --- a/test/generators/markdown/Ocamlary.With5.md +++ b/test/generators/markdown/Ocamlary.With5.md @@ -10,4 +10,4 @@ Module `Ocamlary.With5` -###### module [N](Ocamlary.With5.N.md) \ No newline at end of file +###### module [N](Ocamlary.With5.N.md) diff --git a/test/generators/markdown/Ocamlary.With5.module-type-S.md b/test/generators/markdown/Ocamlary.With5.module-type-S.md index 18ded1cb75..b876e5194a 100644 --- a/test/generators/markdown/Ocamlary.With5.module-type-S.md +++ b/test/generators/markdown/Ocamlary.With5.module-type-S.md @@ -8,4 +8,4 @@ Module type `With5.S` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.With6.md b/test/generators/markdown/Ocamlary.With6.md index 0947fca610..ab3e48a58b 100644 --- a/test/generators/markdown/Ocamlary.With6.md +++ b/test/generators/markdown/Ocamlary.With6.md @@ -6,4 +6,4 @@ Module `Ocamlary.With6` -###### module type [T](Ocamlary.With6.module-type-T.md) \ No newline at end of file +###### module type [T](Ocamlary.With6.module-type-T.md) diff --git a/test/generators/markdown/Ocamlary.With6.module-type-T.md b/test/generators/markdown/Ocamlary.With6.module-type-T.md index ec902a93fa..1691b88d3e 100644 --- a/test/generators/markdown/Ocamlary.With6.module-type-T.md +++ b/test/generators/markdown/Ocamlary.With6.module-type-T.md @@ -8,4 +8,4 @@ Module type `With6.T` -###### module [M](Ocamlary.With6.module-type-T.M.md) \ No newline at end of file +###### module [M](Ocamlary.With6.module-type-T.M.md) diff --git a/test/generators/markdown/Ocamlary.With7.argument-1-X.md b/test/generators/markdown/Ocamlary.With7.argument-1-X.md index 168e444e24..bd350e9261 100644 --- a/test/generators/markdown/Ocamlary.With7.argument-1-X.md +++ b/test/generators/markdown/Ocamlary.With7.argument-1-X.md @@ -8,4 +8,4 @@ Parameter `With7.1-X` -###### module type T \ No newline at end of file +###### module type T diff --git a/test/generators/markdown/Ocamlary.With9.md b/test/generators/markdown/Ocamlary.With9.md index c711c30739..51e82aa01a 100644 --- a/test/generators/markdown/Ocamlary.With9.md +++ b/test/generators/markdown/Ocamlary.With9.md @@ -6,4 +6,4 @@ Module `Ocamlary.With9` -###### module type [S](Ocamlary.With9.module-type-S.md) \ No newline at end of file +###### module type [S](Ocamlary.With9.module-type-S.md) diff --git a/test/generators/markdown/Ocamlary.With9.module-type-S.md b/test/generators/markdown/Ocamlary.With9.module-type-S.md index dab1202597..2e3adbb33c 100644 --- a/test/generators/markdown/Ocamlary.With9.module-type-S.md +++ b/test/generators/markdown/Ocamlary.With9.module-type-S.md @@ -8,4 +8,4 @@ Module type `With9.S` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.empty_class.md b/test/generators/markdown/Ocamlary.empty_class.md index f709ae0824..f024055dda 100644 --- a/test/generators/markdown/Ocamlary.empty_class.md +++ b/test/generators/markdown/Ocamlary.empty_class.md @@ -2,4 +2,4 @@ Ocamlary empty_class -Class `Ocamlary.empty_class` \ No newline at end of file +Class `Ocamlary.empty_class` diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 6863345df7..abd1e964f9 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -5,32 +5,45 @@ Module `Ocamlary` This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: - comment formatting + - unassociated comments + - documentation sections + - module system documentation including 1. submodules + 2. module aliases + 3. module types + 4. module type aliases + 5. modules with signatures + 6. modules with aliased signatures + + A numbered list: 1. 3 + 2. 2 + 3. 1 + David Sheets is the author. @@ -43,13 +56,11 @@ This is some verbatim text: ``` verbatim ``` - This is some verbatim text: ``` [][df[]]}} ``` - Here is some raw LaTeX: $e^{i\pi} = -1$ Here is an index table of `Empty` modules: @@ -114,7 +125,6 @@ An ambiguous, misnamed module type > [Empty](Ocamlary.Empty.md) - A plain module alias of `Empty` ### EmptySig @@ -133,7 +143,6 @@ A plain, empty module signature > [EmptySig](Ocamlary.module-type-EmptySig.md) - A plain, empty module signature alias of @@ -218,7 +227,6 @@ Unary exception constructor over binary tuple > 'a -> 'b - [`a_function`](#type-a_function) is this type and [`a_function`](#val-a_function) is the value below. @@ -227,7 +235,6 @@ Unary exception constructor over binary tuple > x : int -> int - This is `a_function` with param and return type. @parameter x: @@ -240,21 +247,18 @@ This is `a_function` with param and return type. > ( ( int , int ) [a_function](#type-a_function) , ( unit , unit ) [a_function](#type-a_function) ) [a_function](#type-a_function) - ###### val fun_maybe : > ? yes : unit -> unit -> int - ###### val not_found : > unit -> unit - @raises Not_found: @@ -263,7 +267,6 @@ This is `a_function` with param and return type. > string - @see [http://ocaml.org/](http://ocaml.org/): @@ -272,7 +275,6 @@ This is `a_function` with param and return type. > string - @see `some_file`: @@ -281,7 +283,6 @@ This is `a_function` with param and return type. > string - @see some_doc: @@ -290,7 +291,6 @@ This is `a_function` with param and return type. > unit - This value was introduced in the Mesozoic era. @since: mesozoic @@ -301,7 +301,6 @@ This value was introduced in the Mesozoic era. > unit - This value has had changes in 1.0.0, 1.1.0, and 1.2.0. @before 1.0.0: @@ -320,98 +319,84 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. > unit - ###### val (!) : > unit - ###### val (@) : > unit - ###### val ($) : > unit - ###### val (%) : > unit - ###### val (&) : > unit - ###### val (*) : > unit - ###### val (-) : > unit - ###### val (+) : > unit - ###### val (-?) : > unit - ###### val (/) : > unit - ###### val (:=) : > unit - ###### val (=) : > unit - ###### val (land) : > unit - ### Advanced Module Stuff --- @@ -642,7 +627,6 @@ Wow! It was a mixed GADT! > [variant](#type-variant) - This comment is for `alias` . @@ -651,7 +635,6 @@ This comment is for `alias` . > ( [alias](#type-alias) * [alias](#type-alias) ) * [alias](#type-alias) * ( [alias](#type-alias) * [alias](#type-alias) ) - This comment is for `tuple` . @@ -738,49 +721,42 @@ This comment is for `poly_variant_union` . > [> `TagA ] as ' a - ###### type 'a open_poly_variant2 = > [> `ConstrB of int ] as ' a - ###### type 'a open_poly_variant_alias = > 'a [open_poly_variant](#type-open_poly_variant) [open_poly_variant2](#type-open_poly_variant2) - ###### type 'a poly_fun = > [> `ConstrB of int ] as ' a -> 'a - ###### type 'a poly_fun_constraint = > 'a -> 'a constraint 'a = [> `TagA ] - ###### type 'a closed_poly_variant = > [< `One | `Two ] as ' a - ###### type 'a clopen_poly_variant = > [< `One | `Two of int | `Three Two Three ] as ' a - ###### type nested_poly_variant = [ @@ -849,7 +825,6 @@ This comment is for `partial_gadt_alias` . > unit -> exn - This comment is for [`Exn_arrow`](#exception-Exn_arrow) . @@ -890,49 +865,42 @@ This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then [`mutual_con > < f : int ; g : unit -> unit ; h : [rec_obj](#type-rec_obj) > - ###### type 'a open_obj = > < f : int ; g : unit -> unit .. > as ' a - ###### type 'a oof = > < a : unit .. > as ' a -> 'a - ###### type 'a any_obj = > < .. > as ' a - ###### type empty_obj = > < > - ###### type one_meth = > < meth : unit > - ###### type ext = > .. - A mystery wrapped in an ellipsis @@ -985,7 +953,6 @@ A mystery wrapped in an ellipsis > .. - 'a poly_ext @@ -1042,7 +1009,6 @@ and it packs a unit. > unit -> unit - Rotate keys on my mark... @@ -1051,7 +1017,6 @@ Rotate keys on my mark... > ( module [COLLECTION](Ocamlary.module-type-COLLECTION.md) ) - A brown paper package tied up with string @@ -1076,14 +1041,12 @@ A brown paper package tied up with string > unit [param_class](Ocamlary.param_class.md) - ###### type 'a my_unit_class = > unit param_class as ' a - ###### module [Dep1](Ocamlary.Dep1.md) @@ -1098,7 +1061,6 @@ A brown paper package tied up with string > [Dep2(Dep1).B.c](Ocamlary.Dep1.module-type-S.c.md) - ###### module [Dep3](Ocamlary.Dep3.md) @@ -1117,14 +1079,12 @@ A brown paper package tied up with string > [Dep5(Dep4).Z.X.b](Ocamlary.Dep4.module-type-T.md#type-b) - ###### type dep3 = > [Dep5(Dep4).Z.Y.a](Ocamlary.Dep3.md#type-a) - ###### module [Dep6](Ocamlary.Dep6.md) @@ -1139,7 +1099,6 @@ A brown paper package tied up with string > [Dep7(Dep6).M.Y.d](Ocamlary.Dep6.module-type-T.Y.md#type-d) - ###### module [Dep8](Ocamlary.Dep8.md) @@ -1170,7 +1129,6 @@ A brown paper package tied up with string > [Dep13.c](Ocamlary.Dep13.c.md) - ###### module type [With1](Ocamlary.module-type-With1.md) @@ -1189,7 +1147,6 @@ A brown paper package tied up with string > [With3.N.t](Ocamlary.With3.N.md#type-t) - ###### module [With4](Ocamlary.With4.md) @@ -1200,7 +1157,6 @@ A brown paper package tied up with string > [With4.N.t](Ocamlary.With4.N.md#type-t) - ###### module [With5](Ocamlary.With5.md) @@ -1243,7 +1199,6 @@ A brown paper package tied up with string > int - ###### module [DoubleInclude1](Ocamlary.DoubleInclude1.md) @@ -1313,24 +1268,32 @@ Let's imitate jst's layout. I can refer to - `{!section:indexmodules}` : [Trying the {!modules: ...} command.](#indexmodules) + - `{!aliases}` : [Aliases again](#aliases) + But also to things in submodules: - `{!section:SuperSig.SubSigA.subSig}` : [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) + - `{!Aliases.incl}` : [`incl`](Ocamlary.Aliases.md#incl) + And just to make sure we do not mess up: - `{{!section:indexmodules}A}` : [A](#indexmodules) + - `{{!aliases}B}` : [B](#aliases) + - `{{!section:SuperSig.SubSigA.subSig}C}` : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) + - `{{!Aliases.incl}D}` : [D](Ocamlary.Aliases.md#incl) + # New reference syntax @@ -1345,20 +1308,26 @@ And just to make sure we do not mess up: Here goes: - `{!module-M.t}` : [`M.t`](Ocamlary.M.md#type-t) + - `{!module-type-M.t}` : [`M.t`](Ocamlary.module-type-M.md#type-t) + ###### module [Only_a_module](Ocamlary.Only_a_module.md) - `{!Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) + - `{!module-Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) + - `{!module-Only_a_module.type-t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) + - `{!type:Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) + @@ -1370,7 +1339,6 @@ Here goes: > .. - ###### type [new_t](#type-new_t) += @@ -1381,4 +1349,4 @@ Here goes: -###### module type [TypeExtPruned](Ocamlary.module-type-TypeExtPruned.md) \ No newline at end of file +###### module type [TypeExtPruned](Ocamlary.module-type-TypeExtPruned.md) diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md index aa2f1c4aaf..5b10de4487 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md index c69b0a6c19..84bd93d54b 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -16,7 +16,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-A.Q.md#type-collection) - This comment is for `t` . @@ -29,4 +28,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index d352b531ee..d52e10ce0d 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.md b/test/generators/markdown/Ocamlary.module-type-A.Q.md index 5f993f523a..2fa57d8fad 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.module-type-A.md b/test/generators/markdown/Ocamlary.module-type-A.md index 6ff3746430..6f28e59f69 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.md +++ b/test/generators/markdown/Ocamlary.module-type-A.md @@ -10,4 +10,4 @@ Module type `Ocamlary.A` -###### module [Q](Ocamlary.module-type-A.Q.md) \ No newline at end of file +###### module [Q](Ocamlary.module-type-A.Q.md) diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md index 7d5e408943..69021adf6a 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md index a9df265fb5..39e5534e75 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -16,7 +16,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-B.Q.md#type-collection) - This comment is for `t` . @@ -29,4 +28,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index 4af5552673..69e0becaa6 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.md b/test/generators/markdown/Ocamlary.module-type-B.Q.md index 2201312f52..ec3b57ed65 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.module-type-B.md b/test/generators/markdown/Ocamlary.module-type-B.md index c8df57a356..4a6d27826f 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.md +++ b/test/generators/markdown/Ocamlary.module-type-B.md @@ -10,4 +10,4 @@ Module type `Ocamlary.B` -###### module [Q](Ocamlary.module-type-B.Q.md) \ No newline at end of file +###### module [Q](Ocamlary.module-type-B.Q.md) diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md index 54ed708665..7d4b87b20a 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md index c2e58194bc..394e748c92 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -16,7 +16,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-C.Q.md#type-collection) - This comment is for `t` . @@ -29,4 +28,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index 7943f99faf..279e8b202a 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.md b/test/generators/markdown/Ocamlary.module-type-C.Q.md index 2aa4a78b30..9f5c2539c2 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.module-type-C.md b/test/generators/markdown/Ocamlary.module-type-C.md index fa87d25802..6903212f21 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.md +++ b/test/generators/markdown/Ocamlary.module-type-C.md @@ -7,8 +7,10 @@ Module type `Ocamlary.C` This module type includes two signatures. - it includes [`A`](Ocamlary.module-type-A.md) + - it includes [`B`](Ocamlary.module-type-B.md) with some substitution + @@ -18,3 +20,4 @@ This module type includes two signatures. ###### module [Q](Ocamlary.module-type-C.Q.md) + diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md index c242abad8d..07ac3d8934 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md index 5f2fa76cec..a43a92fbd5 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -14,7 +14,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-COLLECTION.md#type-collection) - This comment is for `t` . @@ -27,4 +26,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md index a3d956ff02..f789786411 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md index d0b05f0b4d..ffee29b32a 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.module-type-Empty.md b/test/generators/markdown/Ocamlary.module-type-Empty.md index a339e0c43f..eceadec323 100644 --- a/test/generators/markdown/Ocamlary.module-type-Empty.md +++ b/test/generators/markdown/Ocamlary.module-type-Empty.md @@ -8,4 +8,4 @@ An ambiguous, misnamed module type -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.module-type-EmptySig.md b/test/generators/markdown/Ocamlary.module-type-EmptySig.md index 8ef651b9fc..5e31f3971e 100644 --- a/test/generators/markdown/Ocamlary.module-type-EmptySig.md +++ b/test/generators/markdown/Ocamlary.module-type-EmptySig.md @@ -4,4 +4,4 @@ EmptySig Module type `Ocamlary.EmptySig` -A plain, empty module signature \ No newline at end of file +A plain, empty module signature diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md index 33a361fc40..f45fbcf788 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md @@ -6,4 +6,4 @@ Module type `Ocamlary.IncludeInclude2` -###### type include_include \ No newline at end of file +###### type include_include diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md index 7209ceffc9..fdc75998b8 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md @@ -6,3 +6,4 @@ Module type `Ocamlary.IncludeModuleType` This comment is for `IncludeModuleType` . + diff --git a/test/generators/markdown/Ocamlary.module-type-IncludedB.md b/test/generators/markdown/Ocamlary.module-type-IncludedB.md index e18e984f66..d763ff22d9 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludedB.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludedB.md @@ -6,4 +6,4 @@ Module type `Ocamlary.IncludedB` -###### type s \ No newline at end of file +###### type s diff --git a/test/generators/markdown/Ocamlary.module-type-M.md b/test/generators/markdown/Ocamlary.module-type-M.md index 4645da04fd..efdbfdff6d 100644 --- a/test/generators/markdown/Ocamlary.module-type-M.md +++ b/test/generators/markdown/Ocamlary.module-type-M.md @@ -6,4 +6,4 @@ Module type `Ocamlary.M` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md index d43c606972..6bccec368b 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md index e8f4a5f681..017865d511 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -16,7 +16,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-MMM.C.md#type-collection) - This comment is for `t` . @@ -29,4 +28,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md index ba3047c43b..c754c7e581 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -18,5 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.md index 43d7818a2b..eeb6e220b0 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.md @@ -30,5 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.md b/test/generators/markdown/Ocamlary.module-type-MMM.md index 578b606f82..835d2dbf75 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.md @@ -6,4 +6,4 @@ Module type `Ocamlary.MMM` -###### module [C](Ocamlary.module-type-MMM.C.md) \ No newline at end of file +###### module [C](Ocamlary.module-type-MMM.C.md) diff --git a/test/generators/markdown/Ocamlary.module-type-MissingComment.md b/test/generators/markdown/Ocamlary.module-type-MissingComment.md index d8f3434345..ba4762a885 100644 --- a/test/generators/markdown/Ocamlary.module-type-MissingComment.md +++ b/test/generators/markdown/Ocamlary.module-type-MissingComment.md @@ -8,4 +8,4 @@ An ambiguous, misnamed module type -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md index b7c0f78133..f06831974c 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md @@ -6,4 +6,4 @@ Module type `Ocamlary.NestedInclude1` -###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) \ No newline at end of file +###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md index 8c35d8797d..310e4b1d7a 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md @@ -8,4 +8,4 @@ Module type `NestedInclude1.NestedInclude2` -###### type nested_include \ No newline at end of file +###### type nested_include diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md index 470d378376..f81609df90 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md @@ -6,4 +6,4 @@ Module type `Ocamlary.NestedInclude2` -###### type nested_include \ No newline at end of file +###### type nested_include diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md index 1c085d575b..4d86ef1ca5 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleA'` . > ( unit , unit ) [a_function](Ocamlary.md#type-a_function) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md index 755c03f1bd..9552ae0c18 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -14,7 +14,6 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-RecollectionModule.md#type-collection) - This comment is for `t` . @@ -27,4 +26,4 @@ This comment is for `InnerModuleA'` . ###### module type [InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . \ No newline at end of file +This comment is for `InnerModuleTypeA'` . diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index 6e1f98b7b8..c226f33fc5 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -16,5 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md#type-t) - -This comment is for `t` . \ No newline at end of file +This comment is for `t` . diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md index 5a707ceaee..682be9a3d6 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -10,14 +10,12 @@ Module type `Ocamlary.RecollectionModule` > [CollectionModule.element](Ocamlary.CollectionModule.md#type-element) list - ###### type element = > [CollectionModule.collection](Ocamlary.CollectionModule.md#type-collection) - ###### module [InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) @@ -30,5 +28,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) - -This comment is for `InnerModuleTypeA` . \ No newline at end of file +This comment is for `InnerModuleTypeA` . diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md index cded91ccb3..2fadb0ac77 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md @@ -8,4 +8,4 @@ Module `SigForMod.Inner` -###### module type [Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) \ No newline at end of file +###### module type [Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md index 93be426168..48d1d571e1 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md @@ -6,4 +6,4 @@ Inner Empty -Module type `Inner.Empty` \ No newline at end of file +Module type `Inner.Empty` diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.md index 1a640ea449..c177a6d56f 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.md @@ -8,4 +8,4 @@ There's a signature in a module in this signature. -###### module [Inner](Ocamlary.module-type-SigForMod.Inner.md) \ No newline at end of file +###### module [Inner](Ocamlary.module-type-SigForMod.Inner.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.md index 49e588cc9e..76a9c9ee27 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md @@ -22,4 +22,4 @@ Module type `Ocamlary.SuperSig` -###### module type [SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) \ No newline at end of file +###### module type [SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md index 700b55312b..d2802b1fc3 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-EmptySig.md @@ -8,4 +8,4 @@ Module type `SuperSig.EmptySig` -###### type not_actually_empty \ No newline at end of file +###### type not_actually_empty diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md index ae32c4cb7d..b480de2f88 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-One.md @@ -8,4 +8,4 @@ Module type `SuperSig.One` -###### type two \ No newline at end of file +###### type two diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md index 8ff46b3b5d..bcbd524f78 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md @@ -10,4 +10,4 @@ Module `SubSigA.SubSigAMod` -###### type sub_sig_a_mod \ No newline at end of file +###### type sub_sig_a_mod diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md index 0221d59751..88f14c8da6 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -16,4 +16,4 @@ Module type `SuperSig.SubSigA` -###### module [SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) \ No newline at end of file +###### module [SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md index 23db89975a..3cebb11dd4 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md @@ -12,4 +12,4 @@ Module type `SuperSig.SubSigB` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md index 50be165fdc..315d829ca3 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SuperSig.md @@ -4,4 +4,4 @@ SuperSig SuperSig -Module type `SuperSig.SuperSig` \ No newline at end of file +Module type `SuperSig.SuperSig` diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md index 26d038618d..560c308a0c 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md @@ -8,4 +8,4 @@ Module `ToInclude.IncludedA` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.md index 6a54a48715..9583e397a3 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md @@ -10,4 +10,4 @@ Module type `Ocamlary.ToInclude` -###### module type [IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) \ No newline at end of file +###### module type [IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md index 2a6af20caa..3a3a6d15ff 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.module-type-IncludedB.md @@ -8,4 +8,4 @@ Module type `ToInclude.IncludedB` -###### type s \ No newline at end of file +###### type s diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExt.md b/test/generators/markdown/Ocamlary.module-type-TypeExt.md index 22cfaaa6cb..de2aa58ef5 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExt.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExt.md @@ -10,7 +10,6 @@ Module type `Ocamlary.TypeExt` > .. - ###### type [t](#type-t) += diff --git a/test/generators/markdown/Ocamlary.module-type-With1.M.md b/test/generators/markdown/Ocamlary.module-type-With1.M.md index 431870afcf..2779578daf 100644 --- a/test/generators/markdown/Ocamlary.module-type-With1.M.md +++ b/test/generators/markdown/Ocamlary.module-type-With1.M.md @@ -8,4 +8,4 @@ Module `With1.M` -###### module type S \ No newline at end of file +###### module type S diff --git a/test/generators/markdown/Ocamlary.module-type-With11.md b/test/generators/markdown/Ocamlary.module-type-With11.md index 2067d152bd..e93896f7a9 100644 --- a/test/generators/markdown/Ocamlary.module-type-With11.md +++ b/test/generators/markdown/Ocamlary.module-type-With11.md @@ -10,7 +10,6 @@ Module type `Ocamlary.With11` > [With9](Ocamlary.With9.md) - -###### module [N](Ocamlary.module-type-With11.N.md) \ No newline at end of file +###### module [N](Ocamlary.module-type-With11.N.md) diff --git a/test/generators/markdown/Ocamlary.module-type-With8.M.md b/test/generators/markdown/Ocamlary.module-type-With8.M.md index aee10b7480..2096674b6b 100644 --- a/test/generators/markdown/Ocamlary.module-type-With8.M.md +++ b/test/generators/markdown/Ocamlary.module-type-With8.M.md @@ -12,7 +12,6 @@ Module `With8.M` > [With5.S](Ocamlary.With5.module-type-S.md) - -###### module [N](Ocamlary.module-type-With8.M.N.md) \ No newline at end of file +###### module [N](Ocamlary.module-type-With8.M.N.md) diff --git a/test/generators/markdown/Ocamlary.module-type-With8.md b/test/generators/markdown/Ocamlary.module-type-With8.md index 6a1a856d27..8d46410c6c 100644 --- a/test/generators/markdown/Ocamlary.module-type-With8.md +++ b/test/generators/markdown/Ocamlary.module-type-With8.md @@ -6,4 +6,4 @@ Module type `Ocamlary.With8` -###### module [M](Ocamlary.module-type-With8.M.md) \ No newline at end of file +###### module [M](Ocamlary.module-type-With8.M.md) diff --git a/test/generators/markdown/Ocamlary.two_method_class.md b/test/generators/markdown/Ocamlary.two_method_class.md index 4415b4ce64..0757d89fe2 100644 --- a/test/generators/markdown/Ocamlary.two_method_class.md +++ b/test/generators/markdown/Ocamlary.two_method_class.md @@ -10,7 +10,6 @@ Class `Ocamlary.two_method_class` > [one_method_class](Ocamlary.one_method_class.md) - ###### method undo : diff --git a/test/generators/markdown/Recent.X.md b/test/generators/markdown/Recent.X.md index 485087eb11..96ac669330 100644 --- a/test/generators/markdown/Recent.X.md +++ b/test/generators/markdown/Recent.X.md @@ -10,21 +10,18 @@ Module `Recent.X` > [Z.Y](Recent.Z.Y.md) - ###### type t = > int [Z.Y.X.t](Recent.Z.Y.X.md#type-t) - ###### type u := > int - ###### type v = diff --git a/test/generators/markdown/Recent.Z.Y.X.md b/test/generators/markdown/Recent.Z.Y.X.md index 4456904204..3d83ebbb46 100644 --- a/test/generators/markdown/Recent.Z.Y.X.md +++ b/test/generators/markdown/Recent.Z.Y.X.md @@ -10,4 +10,4 @@ Module `Y.X` -###### type 'a t \ No newline at end of file +###### type 'a t diff --git a/test/generators/markdown/Recent.Z.Y.md b/test/generators/markdown/Recent.Z.Y.md index 734c1fe9f4..b91a2781a6 100644 --- a/test/generators/markdown/Recent.Z.Y.md +++ b/test/generators/markdown/Recent.Z.Y.md @@ -8,4 +8,4 @@ Module `Z.Y` -###### module [X](Recent.Z.Y.X.md) \ No newline at end of file +###### module [X](Recent.Z.Y.X.md) diff --git a/test/generators/markdown/Recent.Z.md b/test/generators/markdown/Recent.Z.md index 8e62fae644..69d9579d66 100644 --- a/test/generators/markdown/Recent.Z.md +++ b/test/generators/markdown/Recent.Z.md @@ -6,4 +6,4 @@ Module `Recent.Z` -###### module [Y](Recent.Z.Y.md) \ No newline at end of file +###### module [Y](Recent.Z.Y.md) diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 8ffa95141f..365d7ce1ac 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -100,14 +100,12 @@ bar > | - ###### type nonrec nonrec_ = > int - ###### type empty_conj = @@ -130,14 +128,12 @@ bar > [< `X of & 'a & int * float ] - ###### val conj : > [< `X of int & [< `B of int & float ] ] - ###### module [Z](Recent.Z.md) @@ -148,4 +144,4 @@ bar -###### module type [PolyS](Recent.module-type-PolyS.md) \ No newline at end of file +###### module type [PolyS](Recent.module-type-PolyS.md) diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index 5dbddabf36..42d61c4c12 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -16,4 +16,4 @@ Module type `Recent.PolyS` ######    `| ` `` `B `` -] \ No newline at end of file +] diff --git a/test/generators/markdown/Recent.module-type-S.md b/test/generators/markdown/Recent.module-type-S.md index f55f8316ff..72958f3ad1 100644 --- a/test/generators/markdown/Recent.module-type-S.md +++ b/test/generators/markdown/Recent.module-type-S.md @@ -2,4 +2,4 @@ Recent S -Module type `Recent.S` \ No newline at end of file +Module type `Recent.S` diff --git a/test/generators/markdown/Recent.module-type-S1.argument-1-_.md b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md index 4032dc6a57..dc92670e19 100644 --- a/test/generators/markdown/Recent.module-type-S1.argument-1-_.md +++ b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md @@ -4,4 +4,4 @@ S1 1-_ -Parameter `S1.1-_` \ No newline at end of file +Parameter `S1.1-_` diff --git a/test/generators/markdown/Recent.module-type-S1.md b/test/generators/markdown/Recent.module-type-S1.md index 700ddc2ba2..502dbaebce 100644 --- a/test/generators/markdown/Recent.module-type-S1.md +++ b/test/generators/markdown/Recent.module-type-S1.md @@ -10,4 +10,4 @@ Module type `Recent.S1` ###### module [_](Recent.module-type-S1.argument-1-_.md) -# Signature \ No newline at end of file +# Signature diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md index 73ffed0090..aab69f9e98 100644 --- a/test/generators/markdown/Recent_impl.B.md +++ b/test/generators/markdown/Recent_impl.B.md @@ -10,4 +10,4 @@ Module `Recent_impl.B` -######    | B \ No newline at end of file +######    | B diff --git a/test/generators/markdown/Recent_impl.Foo.A.md b/test/generators/markdown/Recent_impl.Foo.A.md index a6e8d80b62..23e3c013cd 100644 --- a/test/generators/markdown/Recent_impl.Foo.A.md +++ b/test/generators/markdown/Recent_impl.Foo.A.md @@ -12,4 +12,4 @@ Module `Foo.A` -######    | A \ No newline at end of file +######    | A diff --git a/test/generators/markdown/Recent_impl.Foo.B.md b/test/generators/markdown/Recent_impl.Foo.B.md index 74d5eaecc8..fe482a91e6 100644 --- a/test/generators/markdown/Recent_impl.Foo.B.md +++ b/test/generators/markdown/Recent_impl.Foo.B.md @@ -12,4 +12,4 @@ Module `Foo.B` -######    | B \ No newline at end of file +######    | B diff --git a/test/generators/markdown/Recent_impl.Foo.md b/test/generators/markdown/Recent_impl.Foo.md index 54872db5a2..d139f5aefe 100644 --- a/test/generators/markdown/Recent_impl.Foo.md +++ b/test/generators/markdown/Recent_impl.Foo.md @@ -10,4 +10,4 @@ Module `Recent_impl.Foo` -###### module [B](Recent_impl.Foo.B.md) \ No newline at end of file +###### module [B](Recent_impl.Foo.B.md) diff --git a/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md b/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md index 85817bf2b3..1d33fdde97 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md +++ b/test/generators/markdown/Recent_impl.module-type-S.F.argument-1-_.md @@ -6,4 +6,4 @@ F 1-_ -Parameter `F.1-_` \ No newline at end of file +Parameter `F.1-_` diff --git a/test/generators/markdown/Recent_impl.module-type-S.F.md b/test/generators/markdown/Recent_impl.module-type-S.F.md index 35c05c2c2b..db1a999ceb 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.F.md +++ b/test/generators/markdown/Recent_impl.module-type-S.F.md @@ -16,4 +16,4 @@ Module `S.F` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Recent_impl.module-type-S.X.md b/test/generators/markdown/Recent_impl.module-type-S.X.md index cbbae12c02..910d12c348 100644 --- a/test/generators/markdown/Recent_impl.module-type-S.X.md +++ b/test/generators/markdown/Recent_impl.module-type-S.X.md @@ -4,4 +4,4 @@ S X -Module `S.X` \ No newline at end of file +Module `S.X` diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index 3a9e10295e..27b8b0d566 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -22,7 +22,6 @@ Foo bar. > unit - # Empty section # within a comment @@ -33,4 +32,4 @@ Foo bar. # _This_ `section` **title** has markup -But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. \ No newline at end of file +But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md index 517e085c83..9499c700f4 100644 --- a/test/generators/markdown/Stop.md +++ b/test/generators/markdown/Stop.md @@ -10,7 +10,6 @@ This test cases exercises stop comments. > int - This is normal commented text. The next value is `bar` , and it should be missing from the documentation. There is also an entire module, `M` , which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. diff --git a/test/generators/markdown/Stop_dead_link_doc.Foo.md b/test/generators/markdown/Stop_dead_link_doc.Foo.md index 69df6db5cc..5efb036d5e 100644 --- a/test/generators/markdown/Stop_dead_link_doc.Foo.md +++ b/test/generators/markdown/Stop_dead_link_doc.Foo.md @@ -6,4 +6,4 @@ Module `Stop_dead_link_doc.Foo` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index 6eb73f801e..3ad1455fcd 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -58,4 +58,4 @@ Module `Stop_dead_link_doc` -###### type another_bar_ \ No newline at end of file +###### type another_bar_ diff --git a/test/generators/markdown/Toplevel_comments.Alias.md b/test/generators/markdown/Toplevel_comments.Alias.md index 07fcf6e532..dec012f910 100644 --- a/test/generators/markdown/Toplevel_comments.Alias.md +++ b/test/generators/markdown/Toplevel_comments.Alias.md @@ -10,4 +10,4 @@ Doc of `T` , part 2. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md index d836877fb2..6e09566259 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.M.md @@ -8,4 +8,4 @@ Module `Comments_on_open.M` -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md index 3a8bd528e6..08e68c72b8 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -12,4 +12,4 @@ Module `Toplevel_comments.Comments_on_open` --- -Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works \ No newline at end of file +Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works diff --git a/test/generators/markdown/Toplevel_comments.Include_inline'.md b/test/generators/markdown/Toplevel_comments.Include_inline'.md index 4a4e522121..742539067d 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline'.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline'.md @@ -10,4 +10,4 @@ Doc of `Include_inline` , part 2. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.Include_inline.md b/test/generators/markdown/Toplevel_comments.Include_inline.md index 12cfed60ee..97067354b8 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline.md @@ -8,4 +8,4 @@ Doc of `T` , part 2. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.M''.md b/test/generators/markdown/Toplevel_comments.M''.md index 9b97d858d2..a5a7da1527 100644 --- a/test/generators/markdown/Toplevel_comments.M''.md +++ b/test/generators/markdown/Toplevel_comments.M''.md @@ -6,4 +6,4 @@ Module `Toplevel_comments.M''` Doc of `M''` , part 1. -Doc of `M''` , part 2. \ No newline at end of file +Doc of `M''` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.M'.md b/test/generators/markdown/Toplevel_comments.M'.md index 5a5003a083..876cb421b6 100644 --- a/test/generators/markdown/Toplevel_comments.M'.md +++ b/test/generators/markdown/Toplevel_comments.M'.md @@ -4,4 +4,4 @@ M' Module `Toplevel_comments.M'` -Doc of `M'` from outside \ No newline at end of file +Doc of `M'` from outside diff --git a/test/generators/markdown/Toplevel_comments.M.md b/test/generators/markdown/Toplevel_comments.M.md index c8701628e1..7de0e59083 100644 --- a/test/generators/markdown/Toplevel_comments.M.md +++ b/test/generators/markdown/Toplevel_comments.M.md @@ -4,4 +4,4 @@ M Module `Toplevel_comments.M` -Doc of `M` \ No newline at end of file +Doc of `M` diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md index 2fd084c307..ccb89f1d5c 100644 --- a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -10,4 +10,4 @@ This reference should resolve in the context of this module, even when used as a -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.c1.md b/test/generators/markdown/Toplevel_comments.c1.md index 37bd69b324..d6508a9428 100644 --- a/test/generators/markdown/Toplevel_comments.c1.md +++ b/test/generators/markdown/Toplevel_comments.c1.md @@ -6,4 +6,4 @@ Class `Toplevel_comments.c1` Doc of `c1` , part 1. -Doc of `c1` , part 2. \ No newline at end of file +Doc of `c1` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.c2.md b/test/generators/markdown/Toplevel_comments.c2.md index 56ebb35850..2fa05b16df 100644 --- a/test/generators/markdown/Toplevel_comments.c2.md +++ b/test/generators/markdown/Toplevel_comments.c2.md @@ -6,4 +6,4 @@ Class `Toplevel_comments.c2` Doc of `c2` . -Doc of `ct` , part 2. \ No newline at end of file +Doc of `ct` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.class-type-ct.md b/test/generators/markdown/Toplevel_comments.class-type-ct.md index 851f09edf5..6551211e33 100644 --- a/test/generators/markdown/Toplevel_comments.class-type-ct.md +++ b/test/generators/markdown/Toplevel_comments.class-type-ct.md @@ -6,4 +6,4 @@ Class type `Toplevel_comments.ct` Doc of `ct` , part 1. -Doc of `ct` , part 2. \ No newline at end of file +Doc of `ct` , part 2. diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index aa6f394bea..1e2baa54b8 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -84,4 +84,4 @@ Doc of `c2` . -###### module [Comments_on_open](Toplevel_comments.Comments_on_open.md) \ No newline at end of file +###### module [Comments_on_open](Toplevel_comments.Comments_on_open.md) diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md index 0654cc3620..029629e6c7 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md @@ -10,4 +10,4 @@ Doc of `Include_inline_T'` , part 2. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md index f7b06b85f9..2132463593 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md @@ -8,4 +8,4 @@ Doc of `T` , part 2. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Toplevel_comments.module-type-T.md b/test/generators/markdown/Toplevel_comments.module-type-T.md index 1b9f00fded..276e41836e 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-T.md +++ b/test/generators/markdown/Toplevel_comments.module-type-T.md @@ -10,4 +10,4 @@ Doc of `T` , part 2. -###### type t \ No newline at end of file +###### type t diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 06a444d3be..89a9e243cb 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -14,98 +14,84 @@ Some _documentation_ . > int - ###### type private_ = > private int - ###### type 'a constructor = > 'a - ###### type arrow = > int -> int - ###### type higher_order = > ( int -> int ) -> int - ###### type labeled = > l : int -> int - ###### type optional = > ? l : int -> int - ###### type labeled_higher_order = > ( l : int -> int ) -> ( ? l : int -> int ) -> int - ###### type pair = > int * int - ###### type parens_dropped = > int * int - ###### type triple = > int * int * int - ###### type nested_pair = > ( int * int ) * int - ###### type instance = > int [constructor](#type-constructor) - ###### type long = > [labeled_higher_order](#type-labeled_higher_order) -> [ `Bar | `Baz of [triple](#type-triple) ] -> [pair](#type-pair) -> [labeled](#type-labeled) -> [higher_order](#type-higher_order) -> ( string -> int ) -> ( int * float * char * string * char * unit ) option -> [nested_pair](#type-nested_pair) -> [arrow](#type-arrow) -> string -> [nested_pair](#type-nested_pair) array - ###### type variant_e = { @@ -282,7 +268,6 @@ _bar_ > < a : int ; b : int ; c : int > - ###### module type [X](Type.module-type-X.md) @@ -293,14 +278,12 @@ _bar_ > ( module [X](Type.module-type-X.md) ) - ###### type module_substitution = > ( module [X](Type.module-type-X.md) with type [t](Type.module-type-X.md#type-t) = int and type [u](Type.module-type-X.md#type-u) = unit ) - ###### type +'a covariant @@ -315,7 +298,6 @@ _bar_ > int - ###### type ('a, 'b) binary @@ -326,7 +308,6 @@ _bar_ > ( int , int ) [binary](#type-binary) - ###### type 'custom name @@ -337,84 +318,72 @@ _bar_ > 'a constraint 'a = int - ###### type 'a exact_variant = > 'a constraint 'a = [ `A | `B of int ] - ###### type 'a lower_variant = > 'a constraint 'a = [> `A | `B of int ] - ###### type 'a any_variant = > 'a constraint 'a = [> ] - ###### type 'a upper_variant = > 'a constraint 'a = [< `A | `B of int ] - ###### type 'a named_variant = > 'a constraint 'a = [< [polymorphic_variant](#type-polymorphic_variant) ] - ###### type 'a exact_object = > 'a constraint 'a = < a : int ; b : int > - ###### type 'a lower_object = > 'a constraint 'a = < a : int ; b : int .. > - ###### type 'a poly_object = > 'a constraint 'a = < a : 'a. 'a > - ###### type ('a, 'b) double_constrained = > 'a * 'b constraint 'a = int constraint 'b = unit - ###### type as_ = > int as ' a * 'a - ###### type extensible = > .. - ###### type [extensible](#type-extensible) += @@ -449,4 +418,4 @@ Documentation for [`Another_extension`](#extension-Another_extension) . -###### exception Foo of int * int \ No newline at end of file +###### exception Foo of int * int diff --git a/test/generators/markdown/Type.module-type-X.md b/test/generators/markdown/Type.module-type-X.md index 8b685f4bea..2ba8d30a45 100644 --- a/test/generators/markdown/Type.module-type-X.md +++ b/test/generators/markdown/Type.module-type-X.md @@ -10,4 +10,4 @@ Module type `Type.X` -###### type u \ No newline at end of file +###### type u diff --git a/test/generators/markdown/Val.md b/test/generators/markdown/Val.md index 028900f886..9690ef2106 100644 --- a/test/generators/markdown/Val.md +++ b/test/generators/markdown/Val.md @@ -8,7 +8,6 @@ Module `Val` > unit - Foo. @@ -17,12 +16,10 @@ Foo. > unit - ###### val documented_above : > unit - -Bar. \ No newline at end of file +Bar. diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index 6e0395559b..d5c7b0f803 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -38,4 +38,4 @@ This is another subsection. Another paragraph in subsection 2. -Yet another paragraph in subsection 2. \ No newline at end of file +Yet another paragraph in subsection 2. From 27a972cce2d4db54278523b10e2f245f3d01f3d4 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 7 Feb 2022 17:05:18 +0100 Subject: [PATCH 27/38] Fix rendering of spaces between inlines --- src/markdown/generator.ml | 80 ++++- src/markdown/markup.ml | 12 +- src/markdown/markup.mli | 2 + test/generators/markdown/Alias.X.md | 3 +- test/generators/markdown/Bugs.md | 6 +- test/generators/markdown/Bugs_post_406.md | 7 +- test/generators/markdown/Class.md | 14 +- test/generators/markdown/External.md | 2 +- test/generators/markdown/Include.md | 12 +- .../markdown/Include2.Y_include_synopsis.md | 3 +- test/generators/markdown/Include2.md | 3 +- test/generators/markdown/Include_sections.md | 6 +- test/generators/markdown/Labels.md | 10 +- test/generators/markdown/Markup.md | 61 +++- test/generators/markdown/Module.md | 4 +- .../Module_type_subst.Basic.module-type-u.md | 3 +- .../Module_type_subst.Basic.module-type-u2.md | 3 +- ...ule_type_subst.Basic.module-type-with_2.md | 3 +- .../markdown/Module_type_subst.Nested.md | 3 +- ..._type_subst.Nested.module-type-nested.N.md | 3 +- ...ule_type_subst.Structural.module-type-u.md | 3 +- ....Structural.module-type-u.module-type-a.md | 3 +- ...dule-type-u.module-type-a.module-type-b.md | 3 +- ...dule-type-a.module-type-b.module-type-c.md | 2 +- ...ule_type_subst.Structural.module-type-w.md | 3 +- ....Structural.module-type-w.module-type-a.md | 3 +- ...dule-type-w.module-type-a.module-type-b.md | 3 +- ...dule-type-a.module-type-b.module-type-c.md | 2 +- test/generators/markdown/Nested.F.md | 3 +- test/generators/markdown/Nested.md | 4 +- test/generators/markdown/Ocamlary.Aliases.md | 6 +- .../Ocamlary.CanonicalTest.Base_Tests.md | 6 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 6 +- .../Ocamlary.CollectionModule.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.CollectionModule.md | 8 +- test/generators/markdown/Ocamlary.Dep1.X.Y.md | 2 +- .../markdown/Ocamlary.Dep1.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep11.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.Dep13.md | 2 +- test/generators/markdown/Ocamlary.ExtMod.md | 2 +- ...1-Collection.InnerModuleA.InnerModuleA'.md | 6 +- ...peOf.argument-1-Collection.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- ...ary.FunctorTypeOf.argument-1-Collection.md | 11 +- .../markdown/Ocamlary.FunctorTypeOf.md | 4 +- .../markdown/Ocamlary.IncludeInclude1.md | 6 +- .../markdown/Ocamlary.ModuleWithSignature.md | 3 +- ...Recollection.InnerModuleA.InnerModuleA'.md | 6 +- .../Ocamlary.Recollection.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- ...argument-1-C.InnerModuleA.InnerModuleA'.md | 6 +- ....Recollection.argument-1-C.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../Ocamlary.Recollection.argument-1-C.md | 11 +- .../markdown/Ocamlary.Recollection.md | 8 +- test/generators/markdown/Ocamlary.md | 280 ++++++++++-------- ...ule-type-A.Q.InnerModuleA.InnerModuleA'.md | 6 +- .../Ocamlary.module-type-A.Q.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-A.Q.md | 8 +- ...ule-type-B.Q.InnerModuleA.InnerModuleA'.md | 6 +- .../Ocamlary.module-type-B.Q.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-B.Q.md | 8 +- ...ule-type-C.Q.InnerModuleA.InnerModuleA'.md | 6 +- .../Ocamlary.module-type-C.Q.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-C.Q.md | 8 +- ...e-COLLECTION.InnerModuleA.InnerModuleA'.md | 6 +- ...ary.module-type-COLLECTION.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../Ocamlary.module-type-COLLECTION.md | 8 +- .../Ocamlary.module-type-IncludeModuleType.md | 2 +- ...e-type-MMM.C.InnerModuleA.InnerModuleA'.md | 6 +- ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- .../markdown/Ocamlary.module-type-MMM.C.md | 8 +- .../Ocamlary.module-type-NestedInclude1.md | 3 +- ...ectionModule.InnerModuleA.InnerModuleA'.md | 6 +- ...le-type-RecollectionModule.InnerModuleA.md | 14 +- ...erModuleA.module-type-InnerModuleTypeA'.md | 4 +- ...Ocamlary.module-type-RecollectionModule.md | 7 +- .../Ocamlary.module-type-SigForMod.Inner.md | 3 +- .../markdown/Ocamlary.module-type-SuperSig.md | 12 +- ...odule-type-SuperSig.module-type-SubSigA.md | 3 +- .../Ocamlary.module-type-ToInclude.md | 3 +- .../markdown/Ocamlary.module-type-TypeExt.md | 2 +- .../Ocamlary.module-type-TypeExtPruned.md | 2 +- test/generators/markdown/Recent.md | 26 +- .../markdown/Recent.module-type-PolyS.md | 8 +- test/generators/markdown/Recent_impl.B.md | 2 +- test/generators/markdown/Recent_impl.Foo.A.md | 2 +- test/generators/markdown/Recent_impl.Foo.B.md | 2 +- test/generators/markdown/Section.md | 4 +- test/generators/markdown/Stop.md | 10 +- .../generators/markdown/Stop_dead_link_doc.md | 10 +- .../markdown/Toplevel_comments.Alias.md | 4 +- .../Toplevel_comments.Comments_on_open.md | 3 +- .../Toplevel_comments.Include_inline'.md | 4 +- .../Toplevel_comments.Include_inline.md | 2 +- .../markdown/Toplevel_comments.M''.md | 4 +- .../Toplevel_comments.Ref_in_synopsis.md | 5 +- .../markdown/Toplevel_comments.c1.md | 4 +- .../markdown/Toplevel_comments.c2.md | 4 +- .../Toplevel_comments.class-type-ct.md | 4 +- test/generators/markdown/Toplevel_comments.md | 37 +-- ..._comments.module-type-Include_inline_T'.md | 4 +- ...l_comments.module-type-Include_inline_T.md | 2 +- .../Toplevel_comments.module-type-T.md | 4 +- test/generators/markdown/Type.md | 92 +++--- test/generators/markdown/mld.md | 3 +- 112 files changed, 699 insertions(+), 480 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 8141c16e96..ef5180211b 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -12,6 +12,21 @@ let string_repeat n s = done; Bytes.unsafe_to_string b +(** Like [String.index_from_opt] but check against a predicate function. *) +let rec string_index_f f s i = + if i >= String.length s then None + else if f s.[i] then Some i + else string_index_f f s (i + 1) + +(** Remove spaces at the end of a string. *) +let string_trim_right s = + let right = String.length s - 1 in + let i = ref right in + while !i >= 0 && s.[!i] = ' ' do + decr i + done; + if !i = right then s else String.sub s 0 (!i + 1) + let style (style : style) = match style with | `Bold -> bold @@ -19,8 +34,9 @@ let style (style : style) = | `Superscript -> superscript | `Subscript -> subscript +(** Fold inlines using [join]. *) let fold_inlines f elts : inlines = - List.fold_left (fun acc elt -> acc ++ f elt) noop elts + List.fold_left (fun acc elt -> join acc (f elt)) noop elts let fold_blocks f elts : blocks = List.fold_left (fun acc elt -> acc +++ f elt) noop_block elts @@ -59,16 +75,48 @@ let source_take_until_punctuation code = | ':' | '=' -> true | _ -> false in - let is_punctuation i = - List.exists - (function - | { Inline.desc = Text s; _ } -> is_punctuation s 0 | _ -> false) - i + let rec inline_take_until_punctuation acc = function + | ({ Inline.desc = Text s; _ } as inline) :: tl when is_punctuation s 0 -> + let inline = { inline with desc = Text (string_trim_right s) } in + Some (List.rev (inline :: acc), tl) + | hd :: tl -> inline_take_until_punctuation (hd :: acc) tl + | [] -> None + in + let left, middle, right = + Take.until code ~classify:(function + | Source.Elt i as t -> ( + match inline_take_until_punctuation [] i with + | Some (i, tl) -> Stop_and_accum ([ Source.Elt i ], Some tl) + | None -> Accum [ t ]) + | Tag (_, c) -> Rec c) in - Take.until code ~classify:(function - | Source.Elt i as t -> - if is_punctuation i then Stop_and_accum ([ t ], None) else Accum [ t ] - | Tag (_, c) -> Rec c) + let right = + match middle with Some i -> Source.Elt i :: right | None -> right + in + (left, right) + +let is_not_whitespace = function ' ' -> false | _ -> true + +let rec inline_trim_begin = function + | ({ Inline.desc = Text s; _ } as inline) :: tl -> ( + match string_index_f is_not_whitespace s 0 with + | None -> inline_trim_begin tl + | Some i -> + let s = String.sub s i (String.length s - i) in + { inline with desc = Text s } :: tl) + | x -> x + +(** Remove the spaces at the beginning of source code. *) +let rec source_trim_begin = function + | Source.Elt i :: tl -> ( + match inline_trim_begin i with + | [] -> source_trim_begin tl + | i -> Source.Elt i :: tl) + | Tag (attr, c) :: tl -> ( + match source_trim_begin c with + | [] -> source_trim_begin tl + | c -> Tag (attr, c) :: tl) + | [] -> [] (** Used for code spans. Must be called only on sources that pass [source_contains_only_text s]. *) @@ -96,8 +144,8 @@ and inline l args = fold_inlines (inline_one args) l and inline_one args i = match i.Inline.desc with - | Text ("" | " ") -> noop - | Text s -> text (String.trim s) + | Text " " -> space + | Text s -> text s | Entity _ -> noop | Styled (styl, content) -> style styl (inline content args) | Linebreak -> line_break @@ -265,11 +313,11 @@ and item (l : Item.t list) args nesting_level = match take_code_from_declaration content with | code, [] -> (* Declaration is only code, render formatted code. *) - let code, _, content = source_take_until_punctuation code in + let code, content = source_take_until_punctuation code in let content = - if source_contains_text content then - quote_block (paragraph (source_code content args)) - else noop_block + match source_trim_begin content with + | [] -> noop_block + | content -> quote_block (paragraph (source_code content args)) in render_declaration ~anchor ~doc code content | code, content -> diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 747b1d9ee7..c775c2503c 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -12,6 +12,7 @@ type inlines = | Anchor of string | Linebreak | Noop + | Space type blocks = | ConcatB of blocks * blocks @@ -47,6 +48,8 @@ let line_break = Linebreak let noop = Noop +let space = Space + let bold i = Join (String "**", Join (i, String "**")) let italic i = Join (String "_", Join (i, String "_")) @@ -106,24 +109,21 @@ let rec pp_inlines fmt i = match i with | String s -> Format.fprintf fmt "%s" s | ConcatI (left, right) -> - if left = noop then pp_inlines fmt right - else if right = noop then pp_inlines fmt left - else Format.fprintf fmt "%a %a" pp_inlines left pp_inlines right + Format.fprintf fmt "%a@ %a" pp_inlines left pp_inlines right | Join (left, right) -> Format.fprintf fmt "%a%a" pp_inlines left pp_inlines right | Link (href, i) -> Format.fprintf fmt "[%a](%s)" pp_inlines i href | Anchor s -> Format.fprintf fmt "" s | Linebreak -> Format.fprintf fmt "@\n" | Noop -> () + | Space -> Format.fprintf fmt "@ " let rec pp_blocks fmt b = match b with | ConcatB (Block Noop, b) | ConcatB (b, Block Noop) -> pp_blocks fmt b | ConcatB (above, below) -> Format.fprintf fmt "%a@\n%a" pp_blocks above pp_blocks below - | Block i -> - pp_inlines fmt i; - Format.fprintf fmt "@\n" + | Block i -> Format.fprintf fmt "@[%a@]@\n" pp_inlines i | CodeBlock i -> Format.fprintf fmt "```@\n%a@\n```" pp_inlines i | Block_separator -> Format.fprintf fmt "---@\n" | List (list_type, l) -> diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index 0cfba0cd85..bc93f1ac57 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -15,6 +15,8 @@ val join : inlines -> inlines -> inlines val text : string -> inlines (** An arbitrary string. *) +val space : inlines + val line_break : inlines val noop : inlines diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md index e7dc9b97f6..898ce2802e 100644 --- a/test/generators/markdown/Alias.X.md +++ b/test/generators/markdown/Alias.X.md @@ -10,4 +10,5 @@ Module `Alias.X` > int -Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' +Module Foo__X documentation. This should appear in the documentation for the +alias to this module 'X' diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index 1ce9bca536..ee6dd795d6 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -12,6 +12,8 @@ Module `Bugs` ###### val foo : -> ? bar : 'a -> unit -> unit +> ?bar:'a -> unit -> unit -Triggers an assertion failure when [https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) is not fixed. +Triggers an assertion failure when +[https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) +is not fixed. diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index 6b7b6e3ce4..df49dd87b4 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -2,12 +2,13 @@ Bugs_post_406 Module `Bugs_post_406` -Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 +Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was +added to the language in 4.06 -###### class type [let_open](Bugs_post_406.class-type-let_open.md) +###### class type [let_open](Bugs_post_406.class-type-let_open.md) -###### class [let_open'](Bugs_post_406.let_open'.md) +###### class [let_open'](Bugs_post_406.let_open'.md) diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md index e1d8761c53..a52e6eb12e 100644 --- a/test/generators/markdown/Class.md +++ b/test/generators/markdown/Class.md @@ -4,31 +4,31 @@ Module `Class` -###### class type [empty](Class.class-type-empty.md) +###### class type [empty](Class.class-type-empty.md) -###### class type [mutually](Class.class-type-mutually.md) +###### class type [mutually](Class.class-type-mutually.md) -###### class type [recursive](Class.class-type-recursive.md) +###### class type [recursive](Class.class-type-recursive.md) -###### class [mutually'](Class.mutually'.md) +###### class [mutually'](Class.mutually'.md) -###### class [recursive'](Class.recursive'.md) +###### class [recursive'](Class.recursive'.md) -###### class type virtual [empty_virtual](Class.class-type-empty_virtual.md) +###### class type virtual [empty_virtual](Class.class-type-empty_virtual.md) -###### class virtual [empty_virtual'](Class.empty_virtual'.md) +###### class virtual [empty_virtual'](Class.empty_virtual'.md) diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md index e28b1c5a0e..05b5db0fd7 100644 --- a/test/generators/markdown/External.md +++ b/test/generators/markdown/External.md @@ -8,4 +8,4 @@ Module `External` > unit -> unit -Foo _bar_ . +Foo _bar_. diff --git a/test/generators/markdown/Include.md b/test/generators/markdown/Include.md index f501f79229..46c19b8ce6 100644 --- a/test/generators/markdown/Include.md +++ b/test/generators/markdown/Include.md @@ -20,13 +20,16 @@ Module `Include` -###### module type [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) +###### module type +[Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -include [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) +include +[Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -###### module type [Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) +###### module type +[Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) @@ -38,7 +41,8 @@ include [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -###### module type [Dorminant_Module](Include.module-type-Dorminant_Module.md) +###### module type +[Dorminant_Module](Include.module-type-Dorminant_Module.md) diff --git a/test/generators/markdown/Include2.Y_include_synopsis.md b/test/generators/markdown/Include2.Y_include_synopsis.md index 67210eeb9c..ce0e611349 100644 --- a/test/generators/markdown/Include2.Y_include_synopsis.md +++ b/test/generators/markdown/Include2.Y_include_synopsis.md @@ -4,7 +4,8 @@ Y_include_synopsis Module `Include2.Y_include_synopsis` -The `include Y` below should have the synopsis from `Y` 's top-comment attached to it. +The `include Y` below should have the synopsis from `Y`'s top-comment +attached to it. diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index adbe9eda1f..1feb8a5d95 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -26,7 +26,8 @@ Top-comment of Y. ###### module [Y_include_synopsis](Include2.Y_include_synopsis.md) -The `include Y` below should have the synopsis from `Y` 's top-comment attached to it. +The `include Y` below should have the synopsis from `Y`'s top-comment +attached to it. diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index 593cee3b88..82a8c8d973 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -24,7 +24,8 @@ Some text. # Second include -Let's include [`Something`](Include_sections.module-type-Something.md) a second time: the heading level should be shift here. +Let's include [`Something`](Include_sections.module-type-Something.md) a +second time: the heading level should be shift here. # Something 1 @@ -56,7 +57,8 @@ foo Some text. -And let's include it again, but without inlining it this time: the ToC shouldn't grow. +And let's include it again, but without inlining it this time: the ToC +shouldn't grow. diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index 29f24c37c4..d6ddfcd5fc 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -38,11 +38,11 @@ Attached to external -###### class [c](Labels.c.md) +###### class [c](Labels.c.md) -###### class type [cs](Labels.class-type-cs.md) +###### class type [cs](Labels.class-type-cs.md) @@ -58,7 +58,7 @@ Attached to exception -###### type [x](#type-x) += +###### type [x](#type-x) += @@ -84,7 +84,7 @@ Attached to type subst -###### type u = +###### type u = @@ -98,7 +98,7 @@ Attached to constructor -######    f : [t](#type-t) ; +######    f : [t](#type-t); Attached to field diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index d47b98a60a..86c145f7ac 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -6,7 +6,8 @@ Here, we test the rendering of comment markup. # Sections -Let's get these done first, because sections will be used to break up the rest of this test. +Let's get these done first, because sections will be used to break up the +rest of this test. Besides the section heading above, there are also @@ -20,13 +21,16 @@ and --- -but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. +but odoc has banned deeper headings. There are also title headings, but they +are only allowed in mld files. ### Anchors --- -Sections can have attached [Anchors](#anchors) , and it is possible to [link](#anchors) to them. Links to section headers should not be set in source code style. +Sections can have attached [Anchors](#anchors), and it is possible to +[link](#anchors) to them. Links to section headers should not be set in +source code style. #### Paragraph @@ -38,27 +42,50 @@ Individual paragraphs can have a heading. --- -Parts of a longer paragraph that can be considered alone can also have headings. +Parts of a longer paragraph that can be considered alone can also have +headings. # Styling -This paragraph has some styled elements: **bold** and _italic_ , **_bold italic_** , _emphasis_ , __emphasis_ within emphasis_ , **_bold italic_** , super script , sub script . The line spacing should be enough for superscripts and subscripts not to look odd. +This paragraph has some styled elements: **bold** and _italic_, **_bold +italic_**, _emphasis_, __emphasis_ within emphasis_, **_bold italic_**, +superscript, subscript. The line spacing should be +enough for superscripts and subscripts not to look odd. -Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ emphasis_ is rendered in italics._ _It also work the same in [links in italics with _emphasis _in_ emphasis_ .](#)_ +Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ +emphasis_ is rendered in italics._ _It also work the same in [links in +italics with _emphasis _in_ emphasis_.](#)_ `code` is a different kind of markup that doesn't allow nested markup. -It's possible for two markup elements to appear **next** _to_ each other and have a space, and appear **next** _to_ each other with no space. It doesn't matter **how** _much_ space it was in the source: in this sentence, it was two space characters. And in this one, there is **a** _newline_ . +It's possible for two markup elements to appear **next** _to_ each other and +have a space, and appear **next**_to_ each other with no space. It doesn't +matter **how** _much_ space it was in the source: in this sentence, it was +two space characters. And in this one, there is **a** _newline_. -This is also true between _non-_ `code` markup _and_ `code` . +This is also true between _non-_`code` markup _and_ `code`. -Code can appear **inside `other` markup** . Its display shouldn't be affected. +Code can appear **inside `other` markup**. Its display shouldn't be affected. # Links and references -This is a [link](#) . It sends you to the top of this page. Links can have markup inside them: [**bold**](#) , [_italics_](#) , [_emphasis_](#) , [super script](#) , [sub script](#) , and [`code`](#) . Links can also be nested _[inside](#)_ markup. Links cannot be nested inside each other. This link has no replacement text: [#](#) . The text is filled in by odoc. This is a shorthand link: [#](#) . The text is also filled in by odoc in this case. - -This is a reference to [`foo`](#val-foo) . References can have replacement text: [the value foo](#val-foo) . Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: [**bold**](#val-foo) , [_italic_](#val-foo) , [_emphasis_](#val-foo) , [super script](#val-foo) , [sub script](#val-foo) , and [`code`](#val-foo) . It's also possible to surround a reference in a style: **[`foo`](#val-foo)** . References can't be nested inside references, and links and references can't be nested inside each other. +This is a [link](#). It sends you to the top of this page. Links can have +markup inside them: [**bold**](#), [_italics_](#), [_emphasis_](#), +[superscript](#), [subscript](#), and [`code`](#). +Links can also be nested _[inside](#)_ markup. Links cannot be nested inside +each other. This link has no replacement text: [#](#). The text is filled in +by odoc. This is a shorthand link: [#](#). The text is also filled in by odoc +in this case. + +This is a reference to [`foo`](#val-foo). References can have replacement +text: [the value foo](#val-foo). Except for the special lookup support, +references are pretty much just like links. The replacement text can have +nested styles: [**bold**](#val-foo), [_italic_](#val-foo), +[_emphasis_](#val-foo), [superscript](#val-foo), +[subscript](#val-foo), and [`code`](#val-foo). It's also possible +to surround a reference in a style: **[`foo`](#val-foo)**. References can't +be nested inside references, and links and references can't be nested inside +each other. # Preformatted text @@ -86,7 +113,7 @@ The main difference is these don't get syntax highlighting. - shorthand bulleted list, -- and the paragraphs in each list item support _styling_ . +- and the paragraphs in each list item support _styling_. 1. This is a @@ -95,7 +122,8 @@ The main difference is these don't get syntax highlighting. 2. shorthand numbered list. -- Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break +- Shorthand list items can span multiple lines, however trying to put two + paragraphs into a shorthand list item using a double line break just creates a paragraph outside the list. @@ -136,7 +164,8 @@ The parser supports any ASCII-compatible encoding, in particuλar UTF-8. # Raw HTML -Raw HTML can be as inline elements into sentences. +Raw HTML can be as inline elements +into sentences.
@@ -184,7 +213,7 @@ Each comment can end with zero or more tags. Here are some examples: > unit -Comments in structure items **support** _markup_ , t o o . +Comments in structure items **support** _markup_, too. Some modules to support references. diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index f14ad7d2ae..e91ef0e152 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -10,7 +10,9 @@ Foo. > unit -The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See [https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701) . +The module needs at least one signature item, otherwise a bug causes the +compiler to drop the module comment (above). See +[https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701). diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md index 361821f17f..a7bbdf28bb 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md @@ -8,4 +8,5 @@ Module type `Basic.u` -###### module type [T](Module_type_subst.Basic.module-type-u.module-type-T.md) +###### module type +[T](Module_type_subst.Basic.module-type-u.module-type-T.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md index 8d479a4e08..773fe4a790 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md @@ -8,7 +8,8 @@ Module type `Basic.u2` -###### module type [T](Module_type_subst.Basic.module-type-u2.module-type-T.md) +###### module type +[T](Module_type_subst.Basic.module-type-u2.module-type-T.md) diff --git a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md index 51476ddab2..35b820eab2 100644 --- a/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md +++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md @@ -8,7 +8,8 @@ Module type `Basic.with_2` -###### module type [T](Module_type_subst.Basic.module-type-with_2.module-type-T.md) +###### module type +[T](Module_type_subst.Basic.module-type-with_2.module-type-T.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.md b/test/generators/markdown/Module_type_subst.Nested.md index ff38ef9b26..f2f0dc114b 100644 --- a/test/generators/markdown/Module_type_subst.Nested.md +++ b/test/generators/markdown/Module_type_subst.Nested.md @@ -14,4 +14,5 @@ Module `Module_type_subst.Nested` -###### module type [with_subst](Module_type_subst.Nested.module-type-with_subst.md) +###### module type +[with_subst](Module_type_subst.Nested.module-type-with_subst.md) diff --git a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md index fd24516325..00359a252a 100644 --- a/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md +++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md @@ -10,4 +10,5 @@ Module `nested.N` -###### module type [t](Module_type_subst.Nested.module-type-nested.N.module-type-t.md) +###### module type +[t](Module_type_subst.Nested.module-type-nested.N.module-type-t.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md index 7280e0bd6e..6e840523b4 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md @@ -8,4 +8,5 @@ Module type `Structural.u` -###### module type [a](Module_type_subst.Structural.module-type-u.module-type-a.md) +###### module type +[a](Module_type_subst.Structural.module-type-u.module-type-a.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md index 881b38b441..c2358be43a 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md @@ -10,4 +10,5 @@ Module type `u.a` -###### module type [b](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md) +###### module type +[b](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md index fa75996b71..ef3efc4589 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md @@ -12,4 +12,5 @@ Module type `a.b` -###### module type [c](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md) +###### module type +[c](Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md index 55fc295c8f..8a1a86beba 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.module-type-c.md @@ -14,7 +14,7 @@ Module type `b.c` -###### type t = +###### type t = diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md index 558ef4c443..4202ddbb08 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md @@ -8,4 +8,5 @@ Module type `Structural.w` -###### module type [a](Module_type_subst.Structural.module-type-w.module-type-a.md) +###### module type +[a](Module_type_subst.Structural.module-type-w.module-type-a.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md index 48d151f86b..c3fcb61c87 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md @@ -10,4 +10,5 @@ Module type `w.a` -###### module type [b](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md) +###### module type +[b](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md index 770b469358..18830b5608 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md @@ -12,4 +12,5 @@ Module type `a.b` -###### module type [c](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md) +###### module type +[c](Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md) diff --git a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md index a66176d05d..fcbfa92379 100644 --- a/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md +++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.module-type-c.md @@ -14,7 +14,7 @@ Module type `b.c` -###### type t = +###### type t = diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md index 9fbdebcd09..d9984c3fa4 100644 --- a/test/generators/markdown/Nested.F.md +++ b/test/generators/markdown/Nested.F.md @@ -26,6 +26,7 @@ Some additional comments. ###### type t = -> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) +> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) +> * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) Some type. diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md index a42a9b76bf..6eccd935f9 100644 --- a/test/generators/markdown/Nested.md +++ b/test/generators/markdown/Nested.md @@ -32,10 +32,10 @@ This is a functor F. -###### class virtual [z](Nested.z.md) +###### class virtual [z](Nested.z.md) This is class z. -###### class virtual [inherits](Nested.inherits.md) +###### class virtual [inherits](Nested.inherits.md) diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index d22d259ac9..c8776b354c 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -58,7 +58,8 @@ Let's imitate jst's layout. --- -Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases.Foo.md) . +Just for giggle, let's see what happens when we include +[`Foo`](Ocamlary.Aliases.Foo.md). @@ -94,7 +95,8 @@ Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases > [A.t](Ocamlary.Aliases.Foo.A.md#type-t) -And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and [`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) +And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and +[`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md index 4af17993a5..de7a6f74d2 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md @@ -20,13 +20,15 @@ Module `CanonicalTest.Base_Tests` ###### val foo : -> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float +> [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) ###### val bar : -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a +> [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md index f0bea03d81..0c07f86adc 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md @@ -8,12 +8,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index b3197ff26b..df7fd595e0 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -6,7 +6,7 @@ InnerModuleA Module `CollectionModule.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -14,16 +14,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.CollectionModule.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index 7702b11b16..579f5327ec 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,7 +8,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -16,4 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md index 1b97174584..1ae93f4f70 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.md @@ -4,13 +4,13 @@ CollectionModule Module `Ocamlary.CollectionModule` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -20,7 +20,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.CollectionModule.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -28,4 +28,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.md index af01294c8d..3c5db40a7a 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md @@ -10,4 +10,4 @@ Module `X.Y` -###### class [c](Ocamlary.Dep1.X.Y.c.md) +###### class [c](Ocamlary.Dep1.X.Y.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md index c476643fe3..4bf6502812 100644 --- a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep1.S` -###### class [c](Ocamlary.Dep1.module-type-S.c.md) +###### class [c](Ocamlary.Dep1.module-type-S.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md index 4bfd93a3c3..4dceb4a03b 100644 --- a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep11.S` -###### class [c](Ocamlary.Dep11.module-type-S.c.md) +###### class [c](Ocamlary.Dep11.module-type-S.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep13.md b/test/generators/markdown/Ocamlary.Dep13.md index 9aae84433f..4c3ac1093e 100644 --- a/test/generators/markdown/Ocamlary.Dep13.md +++ b/test/generators/markdown/Ocamlary.Dep13.md @@ -6,4 +6,4 @@ Module `Ocamlary.Dep13` -###### class [c](Ocamlary.Dep13.c.md) +###### class [c](Ocamlary.Dep13.c.md) diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md index 843b94f8fb..aafc1ffb6e 100644 --- a/test/generators/markdown/Ocamlary.ExtMod.md +++ b/test/generators/markdown/Ocamlary.ExtMod.md @@ -12,7 +12,7 @@ Module `Ocamlary.ExtMod` -###### type [t](#type-t) += +###### type [t](#type-t) += diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md index 9d143cf4eb..b9ccc62f50 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md @@ -10,12 +10,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md index d23ba70ece..64ea64131f 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -8,7 +8,7 @@ InnerModuleA Module `1-Collection.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -16,16 +16,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md index 0c967c70dc..c9b6d06b72 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -10,7 +10,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -18,4 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md index 35a1197951..6844d5a9fa 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -6,13 +6,13 @@ FunctorTypeOf Parameter `FunctorTypeOf.1-Collection` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -20,9 +20,10 @@ This comment is for `collection` . -###### module [InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) +###### module +[InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +31,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md index 0e9582178f..7164387808 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md @@ -4,7 +4,7 @@ FunctorTypeOf Module `Ocamlary.FunctorTypeOf` -This comment is for `FunctorTypeOf` . +This comment is for `FunctorTypeOf`. # Parameters @@ -20,4 +20,4 @@ This comment is for `FunctorTypeOf` . > [Collection.collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md index a9ce8a56b0..fcabe29698 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -6,8 +6,10 @@ Module `Ocamlary.IncludeInclude1` -###### module type [IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) +###### module type +[IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) -###### module [IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) +###### module +[IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md index 564f1a2254..025db37fd6 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignature.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md @@ -4,4 +4,5 @@ ModuleWithSignature Module `Ocamlary.ModuleWithSignature` -A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) +A plain module of a signature of +[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md index b27baa577d..b3ad723c6d 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md @@ -8,12 +8,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index 0a488d62e1..ed0a568395 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -6,7 +6,7 @@ InnerModuleA Module `Recollection.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -14,16 +14,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.Recollection.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md index 7b4b4d096c..dec86fd5ee 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,7 +8,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -16,4 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md index c92e5cf3a9..f5a924fc7d 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md @@ -10,12 +10,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md index d2018b6010..4ebb36848f 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -8,7 +8,7 @@ InnerModuleA Module `1-C.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -16,16 +16,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.Recollection.argument-1-C.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md index a118953128..f068446471 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -10,7 +10,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -18,4 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md index c9c28d4e82..4872455f74 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -6,13 +6,13 @@ Recollection Parameter `Recollection.1-C` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -20,9 +20,10 @@ This comment is for `collection` . -###### module [InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) +###### module +[InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +31,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md index 60301a1d57..f262468474 100644 --- a/test/generators/markdown/Ocamlary.Recollection.md +++ b/test/generators/markdown/Ocamlary.Recollection.md @@ -12,7 +12,7 @@ Module `Ocamlary.Recollection` # Signature -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. @@ -20,7 +20,7 @@ This comment is for `CollectionModule` . > [C.element](Ocamlary.Recollection.argument-1-C.md#type-element) list -This comment is for `collection` . +This comment is for `collection`. @@ -32,7 +32,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.Recollection.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -40,4 +40,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index abd1e964f9..96d3fbe428 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -2,7 +2,8 @@ Ocamlary Module `Ocamlary` -This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: +This is an _interface_ with **all** of the _module system_ features. This +documentation demonstrates: - comment formatting @@ -49,7 +50,8 @@ David Sheets is the author. @author: David Sheets -You may find more information about this HTML documentation renderer at [github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary) . +You may find more information about this HTML documentation renderer at +[github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary). This is some verbatim text: @@ -69,15 +71,15 @@ Here is an index table of `Empty` modules: @[`EmptyAlias`](Ocamlary.Empty.md): A plain module alias of `Empty` -Odoc doesn't support `{!indexlist}` . +Odoc doesn't support `{!indexlist}`. -Here is some superscript: x 2 +Here is some superscript: x2 -Here is some subscript: x 0 +Here is some subscript: x0 Here are some escaped brackets: { [ @ ] } -Here is some _emphasis_ `followed by code` . +Here is some _emphasis_ `followed by code`. An unassociated comment @@ -149,11 +151,13 @@ A plain, empty module signature alias of ###### module [ModuleWithSignature](Ocamlary.ModuleWithSignature.md) -A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) +A plain module of a signature of +[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) -###### module [ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) +###### module +[ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) A plain module with an alias signature @@ -171,7 +175,13 @@ There's a signature in a module in this signature. ###### module type [SuperSig](Ocamlary.module-type-SuperSig.md) -For a good time, see [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or [`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) . Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module signature. +For a good time, see +[`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or +[`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or +[`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md). +Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is +the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module +signature. @@ -209,7 +219,8 @@ Unary exception constructor over binary tuple ###### exception EmptySig -[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and [`EmptySig`](#exception-EmptySig) is this exception. +[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and +[`EmptySig`](#exception-EmptySig) is this exception. @@ -227,13 +238,14 @@ Unary exception constructor over binary tuple > 'a -> 'b -[`a_function`](#type-a_function) is this type and [`a_function`](#val-a_function) is the value below. +[`a_function`](#type-a_function) is this type and +[`a_function`](#val-a_function) is the value below. ###### val a_function : -> x : int -> int +> x:int -> int This is `a_function` with param and return type. @@ -245,13 +257,15 @@ This is `a_function` with param and return type. ###### val fun_fun_fun : -> ( ( int , int ) [a_function](#type-a_function) , ( unit , unit ) [a_function](#type-a_function) ) [a_function](#type-a_function) +> +> ( ( int, int ) [a_function](#type-a_function), ( unit, unit ) +> [a_function](#type-a_function) ) [a_function](#type-a_function) ###### val fun_maybe : -> ? yes : unit -> unit -> int +> ?yes:unit -> unit -> int @@ -405,7 +419,7 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. ###### module [CollectionModule](Ocamlary.CollectionModule.md) -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. @@ -427,7 +441,8 @@ module type of -###### module type [RecollectionModule](Ocamlary.module-type-RecollectionModule.md) +###### module type +[RecollectionModule](Ocamlary.module-type-RecollectionModule.md) @@ -447,13 +462,14 @@ This module type includes two signatures. ###### module [FunctorTypeOf](Ocamlary.FunctorTypeOf.md) -This comment is for `FunctorTypeOf` . +This comment is for `FunctorTypeOf`. -###### module type [IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) +###### module type +[IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) -This comment is for `IncludeModuleType` . +This comment is for `IncludeModuleType`. @@ -479,19 +495,19 @@ This comment is for `IncludeModuleType` . ######    `;int : field1` -This comment is for `field1` . +This comment is for `field1`. ######    `;int : field2` -This comment is for `field2` . +This comment is for `field2`. } -This comment is for `record` . +This comment is for `record`. -This comment is also for `record` . +This comment is also for `record`. @@ -523,31 +539,31 @@ This comment is also for `record` . -######    nihilate : 'a. 'a -> unit ; +######    nihilate : 'a. 'a -> unit; } -###### type variant = +###### type variant = ######    | TagA -This comment is for `TagA` . +This comment is for `TagA`. ######    | ConstrB of int -This comment is for `ConstrB` . +This comment is for `ConstrB`. ######    | ConstrC of int * int -This comment is for binary `ConstrC` . +This comment is for binary `ConstrC`. @@ -555,55 +571,55 @@ This comment is for binary `ConstrC` . This comment is for unary `ConstrD` of binary tuple. -This comment is for `variant` . +This comment is for `variant`. -This comment is also for `variant` . +This comment is also for `variant`. -###### type poly_variant = [ +###### type poly_variant = [ -######    `| ` `` `TagA `` +######    `| ``` `TagA `` -######    `| ` `` int of `ConstrB `` +######    `| ``` int of `ConstrB `` -] + ] -This comment is for `poly_variant` . +This comment is for `poly_variant`. Wow! It was a polymorphic variant! -###### type (_, _) full_gadt = +###### type (_, _) full_gadt = -######    | Tag : ( unit , unit ) [full_gadt](#type-full_gadt) +######    | Tag : ( unit, unit ) [full_gadt](#type-full_gadt) -######    | First : 'a -> ( 'a , unit ) [full_gadt](#type-full_gadt) +######    | First : 'a -> ( 'a, unit ) [full_gadt](#type-full_gadt) -######    | Second : 'a -> ( unit , 'a ) [full_gadt](#type-full_gadt) +######    | Second : 'a -> ( unit, 'a ) [full_gadt](#type-full_gadt) -######    | Exist : 'a * 'b -> ( 'b , unit ) [full_gadt](#type-full_gadt) +######    | Exist : 'a * 'b -> ( 'b, unit ) [full_gadt](#type-full_gadt) -This comment is for `full_gadt` . +This comment is for `full_gadt`. Wow! It was a GADT! -###### type 'a partial_gadt = +###### type 'a partial_gadt = @@ -615,9 +631,10 @@ Wow! It was a GADT! -######    | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt](#type-partial_gadt) +######    | ExistGadtTag : ( 'a -> 'b ) -> 'a +[partial_gadt](#type-partial_gadt) -This comment is for `partial_gadt` . +This comment is for `partial_gadt`. Wow! It was a mixed GADT! @@ -627,19 +644,20 @@ Wow! It was a mixed GADT! > [variant](#type-variant) -This comment is for `alias` . +This comment is for `alias`. ###### type tuple = -> ( [alias](#type-alias) * [alias](#type-alias) ) * [alias](#type-alias) * ( [alias](#type-alias) * [alias](#type-alias) ) +> ([alias](#type-alias) * [alias](#type-alias)) * [alias](#type-alias) +> * ([alias](#type-alias) * [alias](#type-alias)) -This comment is for `tuple` . +This comment is for `tuple`. -###### type variant_alias = [variant](#type-variant) = +###### type variant_alias = [variant](#type-variant) = @@ -657,7 +675,7 @@ This comment is for `tuple` . ######    | ConstrD of int * int -This comment is for `variant_alias` . +This comment is for `variant_alias`. @@ -673,71 +691,72 @@ This comment is for `variant_alias` . } -This comment is for `record_alias` . +This comment is for `record_alias`. -###### type poly_variant_union = [ +###### type poly_variant_union = [ -######    `| ` [poly_variant](#type-poly_variant) +######    `| `[poly_variant](#type-poly_variant) -######    `| ` `` `TagC `` +######    `| ``` `TagC `` -] + ] -This comment is for `poly_variant_union` . +This comment is for `poly_variant_union`. -###### type 'a poly_poly_variant = [ +###### type 'a poly_poly_variant = [ -######    `| ` `` 'a of `TagA `` +######    `| ``` 'a of `TagA `` -] + ] -###### type ('a, 'b) bin_poly_poly_variant = [ +###### type ('a, 'b) bin_poly_poly_variant = [ -######    `| ` `` 'a of `TagA `` +######    `| ``` 'a of `TagA `` -######    `| ` `` 'b of `ConstrB `` +######    `| ``` 'b of `ConstrB `` -] + ] ###### type 'a open_poly_variant = -> [> `TagA ] as ' a +> [> `TagA ] as 'a ###### type 'a open_poly_variant2 = -> [> `ConstrB of int ] as ' a +> [> `ConstrB of int ] as 'a ###### type 'a open_poly_variant_alias = -> 'a [open_poly_variant](#type-open_poly_variant) [open_poly_variant2](#type-open_poly_variant2) +> 'a [open_poly_variant](#type-open_poly_variant) +> [open_poly_variant2](#type-open_poly_variant2) ###### type 'a poly_fun = -> [> `ConstrB of int ] as ' a -> 'a +> [> `ConstrB of int ] as 'a -> 'a @@ -749,61 +768,65 @@ This comment is for `poly_variant_union` . ###### type 'a closed_poly_variant = -> [< `One | `Two ] as ' a +> [< `One | `Two ] as 'a ###### type 'a clopen_poly_variant = -> [< `One | `Two of int | `Three Two Three ] as ' a +> [< `One | `Two of int | `Three Two Three ] as 'a -###### type nested_poly_variant = [ +###### type nested_poly_variant = [ -######    `| ` `` `A `` +######    `| ``` `A `` -######    `| ` `` [ `B1 | `B2 ] of `B `` +######    `| ``` [ `B1 | `B2 ] of `B `` -######    `| ` `` `C `` +######    `| ``` `C `` -######    `| ` `` [ [ `D1a ] of`D1 ] of `D `` +######    `| ``` [ [ `D1a ] of`D1 ] of `D `` -] + ] -###### type ('a, 'b) full_gadt_alias = ( 'a , 'b ) [full_gadt](#type-full_gadt) = +###### type ('a, 'b) full_gadt_alias = ( 'a, 'b ) +[full_gadt](#type-full_gadt) = -######    | Tag : ( unit , unit ) [full_gadt_alias](#type-full_gadt_alias) +######    | Tag : ( unit, unit ) [full_gadt_alias](#type-full_gadt_alias) -######    | First : 'a -> ( 'a , unit ) [full_gadt_alias](#type-full_gadt_alias) +######    | First : 'a -> ( 'a, unit ) +[full_gadt_alias](#type-full_gadt_alias) -######    | Second : 'a -> ( unit , 'a ) [full_gadt_alias](#type-full_gadt_alias) +######    | Second : 'a -> ( unit, 'a ) +[full_gadt_alias](#type-full_gadt_alias) -######    | Exist : 'a * 'b -> ( 'b , unit ) [full_gadt_alias](#type-full_gadt_alias) +######    | Exist : 'a * 'b -> ( 'b, unit ) +[full_gadt_alias](#type-full_gadt_alias) -This comment is for `full_gadt_alias` . +This comment is for `full_gadt_alias`. -###### type 'a partial_gadt_alias = 'a [partial_gadt](#type-partial_gadt) = +###### type 'a partial_gadt_alias = 'a [partial_gadt](#type-partial_gadt) = @@ -815,9 +838,10 @@ This comment is for `full_gadt_alias` . -######    | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt_alias](#type-partial_gadt_alias) +######    | ExistGadtTag : ( 'a -> 'b ) -> 'a +[partial_gadt_alias](#type-partial_gadt_alias) -This comment is for `partial_gadt_alias` . +This comment is for `partial_gadt_alias`. @@ -825,11 +849,11 @@ This comment is for `partial_gadt_alias` . > unit -> exn -This comment is for [`Exn_arrow`](#exception-Exn_arrow) . +This comment is for [`Exn_arrow`](#exception-Exn_arrow). -###### type mutual_constr_a = +###### type mutual_constr_a = @@ -839,13 +863,15 @@ This comment is for [`Exn_arrow`](#exception-Exn_arrow) . ######    | B_ish of [mutual_constr_b](#type-mutual_constr_b) -This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and [`mutual_constr_b`](#type-mutual_constr_b) . +This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and +[`mutual_constr_b`](#type-mutual_constr_b). -This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then [`mutual_constr_b`](#type-mutual_constr_b) . +This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then +[`mutual_constr_b`](#type-mutual_constr_b). -###### and mutual_constr_b = +###### and mutual_constr_b = @@ -857,7 +883,8 @@ This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then [`mutual_con This comment must be here for the next to associate correctly. -This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then [`mutual_constr_a`](#type-mutual_constr_a) . +This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then +[`mutual_constr_a`](#type-mutual_constr_a). @@ -869,25 +896,25 @@ This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then [`mutual_con ###### type 'a open_obj = -> < f : int ; g : unit -> unit .. > as ' a +> < f : int ; g : unit -> unit.. > as 'a ###### type 'a oof = -> < a : unit .. > as ' a -> 'a +> < a : unit.. > as 'a -> 'a ###### type 'a any_obj = -> < .. > as ' a +> < .. > as 'a ###### type empty_obj = -> < > +> < > @@ -905,7 +932,7 @@ A mystery wrapped in an ellipsis -###### type [ext](#type-ext) += +###### type [ext](#type-ext) += @@ -913,7 +940,7 @@ A mystery wrapped in an ellipsis -###### type [ext](#type-ext) += +###### type [ext](#type-ext) += @@ -921,7 +948,7 @@ A mystery wrapped in an ellipsis -###### type [ext](#type-ext) += +###### type [ext](#type-ext) += @@ -933,7 +960,7 @@ A mystery wrapped in an ellipsis -###### type [ext](#type-ext) += +###### type [ext](#type-ext) += @@ -941,7 +968,7 @@ A mystery wrapped in an ellipsis -###### type [ext](#type-ext) += +###### type [ext](#type-ext) += @@ -957,7 +984,7 @@ A mystery wrapped in an ellipsis -###### type [poly_ext](#type-poly_ext) += +###### type [poly_ext](#type-poly_ext) += @@ -971,7 +998,7 @@ A mystery wrapped in an ellipsis -###### type [poly_ext](#type-poly_ext) += +###### type [poly_ext](#type-poly_ext) += @@ -985,7 +1012,7 @@ A mystery wrapped in an ellipsis -###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += +###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += @@ -995,7 +1022,7 @@ It's got the rock -###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += +###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += @@ -1015,21 +1042,21 @@ Rotate keys on my mark... ###### type my_mod = -> ( module [COLLECTION](Ocamlary.module-type-COLLECTION.md) ) +> (module [COLLECTION](Ocamlary.module-type-COLLECTION.md)) A brown paper package tied up with string -###### class [empty_class](Ocamlary.empty_class.md) +###### class [empty_class](Ocamlary.empty_class.md) -###### class [one_method_class](Ocamlary.one_method_class.md) +###### class [one_method_class](Ocamlary.one_method_class.md) -###### class [two_method_class](Ocamlary.two_method_class.md) +###### class [two_method_class](Ocamlary.two_method_class.md) @@ -1045,7 +1072,7 @@ A brown paper package tied up with string ###### type 'a my_unit_class = -> unit param_class as ' a +> unit param_class as 'a @@ -1229,15 +1256,18 @@ A brown paper package tied up with string # Trying the {!modules: ...} command. -With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references. +With ocamldoc, toplevel units will be linked and documented, while submodules +will behave as simple references. -With odoc, everything should be resolved (and linked) but only toplevel units will be documented. +With odoc, everything should be resolved (and linked) but only toplevel units +will be documented. @[`Dep1.X`](Ocamlary.Dep1.X.md): @[`Ocamlary.IncludeInclude1`](Ocamlary.IncludeInclude1.md): -@[`Ocamlary`](): This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: +@[`Ocamlary`](): This is an _interface_ with **all** of the _module system_ +features. This documentation demonstrates: ### Weirder usages involving module types @@ -1253,7 +1283,12 @@ With odoc, everything should be resolved (and linked) but only toplevel units wi ###### module [CanonicalTest](Ocamlary.CanonicalTest.md) -Some ref to [`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) and [`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id) . But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) +Some ref to +[`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) +and +[`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id). +But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) +and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) # Aliases again @@ -1267,7 +1302,8 @@ Let's imitate jst's layout. I can refer to -- `{!section:indexmodules}` : [Trying the {!modules: ...} command.](#indexmodules) +- `{!section:indexmodules}` : [Trying the {!modules: ...} + command.](#indexmodules) - `{!aliases}` : [Aliases again](#aliases) @@ -1275,7 +1311,8 @@ I can refer to But also to things in submodules: -- `{!section:SuperSig.SubSigA.subSig}` : [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{!section:SuperSig.SubSigA.subSig}` : + [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) - `{!Aliases.incl}` : [`incl`](Ocamlary.Aliases.md#incl) @@ -1289,7 +1326,8 @@ And just to make sure we do not mess up: - `{{!aliases}B}` : [B](#aliases) -- `{{!section:SuperSig.SubSigA.subSig}C}` : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{{!section:SuperSig.SubSigA.subSig}C}` : + [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) - `{{!Aliases.incl}D}` : [D](Ocamlary.Aliases.md#incl) @@ -1317,16 +1355,20 @@ Here goes: ###### module [Only_a_module](Ocamlary.Only_a_module.md) -- `{!Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!Only_a_module.t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!module-Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!module-Only_a_module.type-t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.type-t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!type:Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!type:Only_a_module.t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) @@ -1341,7 +1383,7 @@ Here goes: -###### type [new_t](#type-new_t) += +###### type [new_t](#type-new_t) += diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md index 5b10de4487..abcc142eaa 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md @@ -10,12 +10,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md index 84bd93d54b..888457b937 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -8,7 +8,7 @@ InnerModuleA Module `Q.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -16,16 +16,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-A.Q.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index d52e10ce0d..21bb568bc7 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -10,7 +10,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -18,4 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.md b/test/generators/markdown/Ocamlary.module-type-A.Q.md index 2fa57d8fad..f32503e3c8 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.md @@ -6,13 +6,13 @@ Q Module `A.Q` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -22,7 +22,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.module-type-A.Q.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md index 69021adf6a..331ba88661 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md @@ -10,12 +10,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md index 39e5534e75..8ba3ae9960 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -8,7 +8,7 @@ InnerModuleA Module `Q.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -16,16 +16,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-B.Q.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index 69e0becaa6..9604560ffa 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -10,7 +10,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -18,4 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.md b/test/generators/markdown/Ocamlary.module-type-B.Q.md index ec3b57ed65..4cb1188255 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.md @@ -6,13 +6,13 @@ Q Module `B.Q` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -22,7 +22,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.module-type-B.Q.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md index 7d4b87b20a..a6a61bf93a 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md @@ -10,12 +10,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md index 394e748c92..7fb5375ddc 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -8,7 +8,7 @@ InnerModuleA Module `Q.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -16,16 +16,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-C.Q.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md index 279e8b202a..d4a28ea8a8 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -10,7 +10,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -18,4 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.md b/test/generators/markdown/Ocamlary.module-type-C.Q.md index 9f5c2539c2..60b4fd80c7 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.md @@ -6,13 +6,13 @@ Q Module `C.Q` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -22,7 +22,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.module-type-C.Q.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md index 07ac3d8934..8f72879b93 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md @@ -8,12 +8,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md index a43a92fbd5..4cb1c304e0 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -6,7 +6,7 @@ InnerModuleA Module `COLLECTION.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -14,16 +14,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-COLLECTION.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md index f789786411..14942cd3ca 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,7 +8,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -16,4 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md index ffee29b32a..89eb207813 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md @@ -6,13 +6,13 @@ Module type `Ocamlary.COLLECTION` module type of -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -22,7 +22,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.module-type-COLLECTION.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md index fdc75998b8..70df33c53d 100644 --- a/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md +++ b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md @@ -4,6 +4,6 @@ IncludeModuleType Module type `Ocamlary.IncludeModuleType` -This comment is for `IncludeModuleType` . +This comment is for `IncludeModuleType`. diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md index 6bccec368b..408bc59f69 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md @@ -10,12 +10,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md index 017865d511..213099c295 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -8,7 +8,7 @@ InnerModuleA Module `C.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -16,16 +16,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-MMM.C.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md index c754c7e581..4b12bcaa97 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -10,7 +10,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -18,4 +18,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.md index eeb6e220b0..c0dd90010c 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.md @@ -6,13 +6,13 @@ C Module `MMM.C` -This comment is for `CollectionModule` . +This comment is for `CollectionModule`. ###### type collection -This comment is for `collection` . +This comment is for `collection`. @@ -22,7 +22,7 @@ This comment is for `collection` . ###### module [InnerModuleA](Ocamlary.module-type-MMM.C.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -30,4 +30,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md index f06831974c..97726c9f67 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md @@ -6,4 +6,5 @@ Module type `Ocamlary.NestedInclude1` -###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) +###### module type +[NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md index 4d86ef1ca5..4a3e052079 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md @@ -8,12 +8,12 @@ InnerModuleA' Module `InnerModuleA.InnerModuleA'` -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. ###### type t = -> ( unit , unit ) [a_function](Ocamlary.md#type-a_function) +> ( unit, unit ) [a_function](Ocamlary.md#type-a_function) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md index 9552ae0c18..8b2ecda941 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -6,7 +6,7 @@ InnerModuleA Module `RecollectionModule.InnerModuleA` -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -14,16 +14,18 @@ This comment is for `InnerModuleA` . > [collection](Ocamlary.module-type-RecollectionModule.md#type-collection) -This comment is for `t` . +This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) -This comment is for `InnerModuleA'` . +This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md index c226f33fc5..bf1a7d398b 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md @@ -8,7 +8,7 @@ InnerModuleTypeA' Module type `InnerModuleA.InnerModuleTypeA'` -This comment is for `InnerModuleTypeA'` . +This comment is for `InnerModuleTypeA'`. @@ -16,4 +16,4 @@ This comment is for `InnerModuleTypeA'` . > [InnerModuleA'.t](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md#type-t) -This comment is for `t` . +This comment is for `t`. diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md index 682be9a3d6..c5ae6dad29 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -18,9 +18,10 @@ Module type `Ocamlary.RecollectionModule` -###### module [InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) +###### module +[InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) -This comment is for `InnerModuleA` . +This comment is for `InnerModuleA`. @@ -28,4 +29,4 @@ This comment is for `InnerModuleA` . > [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) -This comment is for `InnerModuleTypeA` . +This comment is for `InnerModuleTypeA`. diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md index 2fadb0ac77..2aee21fad4 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md @@ -8,4 +8,5 @@ Module `SigForMod.Inner` -###### module type [Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) +###### module type +[Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.md index 76a9c9ee27..cc52b8ba66 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md @@ -6,15 +6,18 @@ Module type `Ocamlary.SuperSig` -###### module type [SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) +###### module type +[SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) -###### module type [SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) +###### module type +[SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) -###### module type [EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) +###### module type +[EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) @@ -22,4 +25,5 @@ Module type `Ocamlary.SuperSig` -###### module type [SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) +###### module type +[SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md index 88f14c8da6..76590cb4d3 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -16,4 +16,5 @@ Module type `SuperSig.SubSigA` -###### module [SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) +###### module +[SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.md index 9583e397a3..f4e70e5a10 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md @@ -10,4 +10,5 @@ Module type `Ocamlary.ToInclude` -###### module type [IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) +###### module type +[IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExt.md b/test/generators/markdown/Ocamlary.module-type-TypeExt.md index de2aa58ef5..a405463f4e 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExt.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExt.md @@ -12,7 +12,7 @@ Module type `Ocamlary.TypeExt` -###### type [t](#type-t) += +###### type [t](#type-t) += diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md index 82cead7046..b17195a0fc 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md @@ -6,7 +6,7 @@ Module type `Ocamlary.TypeExtPruned` -###### type [new_t](Ocamlary.md#type-new_t) += +###### type [new_t](Ocamlary.md#type-new_t) += diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 365d7ce1ac..7c301c6aa8 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -12,7 +12,7 @@ Module `Recent` -###### type variant = +###### type variant = @@ -46,7 +46,7 @@ _bar_ -###### type _ gadt = +###### type _ gadt = @@ -70,29 +70,29 @@ foo -###### type polymorphic_variant = [ +###### type polymorphic_variant = [ -######    `| ` `` `A `` +######    `| ``` `A `` -######    `| ` `` int of `B `` +######    `| ``` int of `B `` -######    `| ` `` `C `` +######    `| ``` `C `` foo -######    `| ` `` `D `` +######    `| ``` `D `` bar -] + ] @@ -108,19 +108,21 @@ bar -###### type empty_conj = +###### type empty_conj = -######    | X : [< `X of & 'a & int * float ] -> [empty_conj](#type-empty_conj) +######    | X : [< `X of & 'a & int * float ] -> +[empty_conj](#type-empty_conj) -###### type conj = +###### type conj = -######    | X : [< `X of int & [< `B of int & float ] ] -> [conj](#type-conj) +######    | X : [< `X of int & [< `B of int & float ] ] -> +[conj](#type-conj) diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index 42d61c4c12..a43c0873b9 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -6,14 +6,14 @@ Module type `Recent.PolyS` -###### type t = [ +###### type t = [ -######    `| ` `` `A `` +######    `| ``` `A `` -######    `| ` `` `B `` +######    `| ``` `B `` -] + ] diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md index aab69f9e98..c0cd07c3fd 100644 --- a/test/generators/markdown/Recent_impl.B.md +++ b/test/generators/markdown/Recent_impl.B.md @@ -6,7 +6,7 @@ Module `Recent_impl.B` -###### type t = +###### type t = diff --git a/test/generators/markdown/Recent_impl.Foo.A.md b/test/generators/markdown/Recent_impl.Foo.A.md index 23e3c013cd..fd2b009318 100644 --- a/test/generators/markdown/Recent_impl.Foo.A.md +++ b/test/generators/markdown/Recent_impl.Foo.A.md @@ -8,7 +8,7 @@ Module `Foo.A` -###### type t = +###### type t = diff --git a/test/generators/markdown/Recent_impl.Foo.B.md b/test/generators/markdown/Recent_impl.Foo.B.md index fe482a91e6..609c159967 100644 --- a/test/generators/markdown/Recent_impl.Foo.B.md +++ b/test/generators/markdown/Recent_impl.Foo.B.md @@ -8,7 +8,7 @@ Module `Foo.B` -###### type t = +###### type t = diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index 27b8b0d566..ff8bfee975 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -32,4 +32,6 @@ Foo bar. # _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. +But links are impossible thanks to the parser, so we never have trouble +rendering a section title in a table of contents – no link will be nested +inside another link. diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md index 9499c700f4..10df64d1f7 100644 --- a/test/generators/markdown/Stop.md +++ b/test/generators/markdown/Stop.md @@ -12,11 +12,17 @@ This test cases exercises stop comments. This is normal commented text. -The next value is `bar` , and it should be missing from the documentation. There is also an entire module, `M` , which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. +The next value is `bar`, and it should be missing from the documentation. +There is also an entire module, `M`, which should also be hidden. It contains +a nested stop comment, but that stop comment should not turn documentation +back on in this outer module, because stop comments respect scope. Documentation is on again. -Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module. +Now, we have a nested module, and it has a stop comment between its two +items. We want to see that the first item is displayed, but the second is +missing, and the stop comment disables documenation only in that module, and +not in this outer module. diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index 3ad1455fcd..ce38008812 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -8,7 +8,7 @@ Module `Stop_dead_link_doc` -###### type foo = +###### type foo = @@ -16,7 +16,7 @@ Module `Stop_dead_link_doc` -###### type bar = +###### type bar = @@ -24,13 +24,13 @@ Module `Stop_dead_link_doc` -######      field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t) ; +######      field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t); } -###### type foo_ = +###### type foo_ = @@ -38,7 +38,7 @@ Module `Stop_dead_link_doc` -###### type bar_ = +###### type bar_ = diff --git a/test/generators/markdown/Toplevel_comments.Alias.md b/test/generators/markdown/Toplevel_comments.Alias.md index dec012f910..dafaaf7973 100644 --- a/test/generators/markdown/Toplevel_comments.Alias.md +++ b/test/generators/markdown/Toplevel_comments.Alias.md @@ -4,9 +4,9 @@ Alias Module `Toplevel_comments.Alias` -Doc of `Alias` . +Doc of `Alias`. -Doc of `T` , part 2. +Doc of `T`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md index 08e68c72b8..c2aea27441 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -12,4 +12,5 @@ Module `Toplevel_comments.Comments_on_open` --- -Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works +Comments attached to open are treated as floating comments. Referencing +[Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works diff --git a/test/generators/markdown/Toplevel_comments.Include_inline'.md b/test/generators/markdown/Toplevel_comments.Include_inline'.md index 742539067d..9c34bb0b4d 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline'.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline'.md @@ -4,9 +4,9 @@ Include_inline' Module `Toplevel_comments.Include_inline'` -Doc of `Include_inline` , part 1. +Doc of `Include_inline`, part 1. -Doc of `Include_inline` , part 2. +Doc of `Include_inline`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.Include_inline.md b/test/generators/markdown/Toplevel_comments.Include_inline.md index 97067354b8..28f67e8d93 100644 --- a/test/generators/markdown/Toplevel_comments.Include_inline.md +++ b/test/generators/markdown/Toplevel_comments.Include_inline.md @@ -4,7 +4,7 @@ Include_inline Module `Toplevel_comments.Include_inline` -Doc of `T` , part 2. +Doc of `T`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.M''.md b/test/generators/markdown/Toplevel_comments.M''.md index a5a7da1527..f9d706a980 100644 --- a/test/generators/markdown/Toplevel_comments.M''.md +++ b/test/generators/markdown/Toplevel_comments.M''.md @@ -4,6 +4,6 @@ M'' Module `Toplevel_comments.M''` -Doc of `M''` , part 1. +Doc of `M''`, part 1. -Doc of `M''` , part 2. +Doc of `M''`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md index ccb89f1d5c..40045252ec 100644 --- a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -4,9 +4,10 @@ Ref_in_synopsis Module `Toplevel_comments.Ref_in_synopsis` -[`t`](#type-t) . +[`t`](#type-t). -This reference should resolve in the context of this module, even when used as a synopsis. +This reference should resolve in the context of this module, even when used +as a synopsis. diff --git a/test/generators/markdown/Toplevel_comments.c1.md b/test/generators/markdown/Toplevel_comments.c1.md index d6508a9428..915599be77 100644 --- a/test/generators/markdown/Toplevel_comments.c1.md +++ b/test/generators/markdown/Toplevel_comments.c1.md @@ -4,6 +4,6 @@ c1 Class `Toplevel_comments.c1` -Doc of `c1` , part 1. +Doc of `c1`, part 1. -Doc of `c1` , part 2. +Doc of `c1`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.c2.md b/test/generators/markdown/Toplevel_comments.c2.md index 2fa05b16df..8eb1ba95ec 100644 --- a/test/generators/markdown/Toplevel_comments.c2.md +++ b/test/generators/markdown/Toplevel_comments.c2.md @@ -4,6 +4,6 @@ c2 Class `Toplevel_comments.c2` -Doc of `c2` . +Doc of `c2`. -Doc of `ct` , part 2. +Doc of `ct`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.class-type-ct.md b/test/generators/markdown/Toplevel_comments.class-type-ct.md index 6551211e33..306fc65cb7 100644 --- a/test/generators/markdown/Toplevel_comments.class-type-ct.md +++ b/test/generators/markdown/Toplevel_comments.class-type-ct.md @@ -4,6 +4,6 @@ ct Class type `Toplevel_comments.ct` -Doc of `ct` , part 1. +Doc of `ct`, part 1. -Doc of `ct` , part 2. +Doc of `ct`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index 1e2baa54b8..5427a97976 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -2,37 +2,40 @@ Toplevel_comments Module `Toplevel_comments` -A doc comment at the beginning of a module is considered to be that module's doc. +A doc comment at the beginning of a module is considered to be that module's +doc. ###### module type [T](Toplevel_comments.module-type-T.md) -Doc of `T` , part 1. +Doc of `T`, part 1. ###### module [Include_inline](Toplevel_comments.Include_inline.md) -Doc of `T` , part 2. +Doc of `T`, part 2. ###### module [Include_inline'](Toplevel_comments.Include_inline'.md) -Doc of `Include_inline` , part 1. +Doc of `Include_inline`, part 1. -###### module type [Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) +###### module type +[Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) -Doc of `T` , part 2. +Doc of `T`, part 2. -###### module type [Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) +###### module type +[Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) -Doc of `Include_inline_T'` , part 1. +Doc of `Include_inline_T'`, part 1. @@ -50,37 +53,37 @@ Doc of `M'` from outside ###### module [M''](Toplevel_comments.M''.md) -Doc of `M''` , part 1. +Doc of `M''`, part 1. ###### module [Alias](Toplevel_comments.Alias.md) -Doc of `Alias` . +Doc of `Alias`. -###### class [c1](Toplevel_comments.c1.md) +###### class [c1](Toplevel_comments.c1.md) -Doc of `c1` , part 1. +Doc of `c1`, part 1. -###### class type [ct](Toplevel_comments.class-type-ct.md) +###### class type [ct](Toplevel_comments.class-type-ct.md) -Doc of `ct` , part 1. +Doc of `ct`, part 1. -###### class [c2](Toplevel_comments.c2.md) +###### class [c2](Toplevel_comments.c2.md) -Doc of `c2` . +Doc of `c2`. ###### module [Ref_in_synopsis](Toplevel_comments.Ref_in_synopsis.md) -[`t`](Toplevel_comments.Ref_in_synopsis.md#type-t) . +[`t`](Toplevel_comments.Ref_in_synopsis.md#type-t). diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md index 029629e6c7..6e53b84362 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T'.md @@ -4,9 +4,9 @@ Include_inline_T' Module type `Toplevel_comments.Include_inline_T'` -Doc of `Include_inline_T'` , part 1. +Doc of `Include_inline_T'`, part 1. -Doc of `Include_inline_T'` , part 2. +Doc of `Include_inline_T'`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md index 2132463593..fdd9c50c68 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md +++ b/test/generators/markdown/Toplevel_comments.module-type-Include_inline_T.md @@ -4,7 +4,7 @@ Include_inline_T Module type `Toplevel_comments.Include_inline_T` -Doc of `T` , part 2. +Doc of `T`, part 2. diff --git a/test/generators/markdown/Toplevel_comments.module-type-T.md b/test/generators/markdown/Toplevel_comments.module-type-T.md index 276e41836e..d50c92b098 100644 --- a/test/generators/markdown/Toplevel_comments.module-type-T.md +++ b/test/generators/markdown/Toplevel_comments.module-type-T.md @@ -4,9 +4,9 @@ T Module type `Toplevel_comments.T` -Doc of `T` , part 1. +Doc of `T`, part 1. -Doc of `T` , part 2. +Doc of `T`, part 2. diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 89a9e243cb..cc01ba4542 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -6,7 +6,7 @@ Module `Type` ###### type abstract -Some _documentation_ . +Some _documentation_. @@ -42,19 +42,19 @@ Some _documentation_ . ###### type labeled = -> l : int -> int +> l:int -> int ###### type optional = -> ? l : int -> int +> ?l:int -> int ###### type labeled_higher_order = -> ( l : int -> int ) -> ( ? l : int -> int ) -> int +> ( l:int -> int ) -> ( ?l:int -> int ) -> int @@ -78,7 +78,7 @@ Some _documentation_ . ###### type nested_pair = -> ( int * int ) * int +> (int * int) * int @@ -90,7 +90,23 @@ Some _documentation_ . ###### type long = -> [labeled_higher_order](#type-labeled_higher_order) -> [ `Bar | `Baz of [triple](#type-triple) ] -> [pair](#type-pair) -> [labeled](#type-labeled) -> [higher_order](#type-higher_order) -> ( string -> int ) -> ( int * float * char * string * char * unit ) option -> [nested_pair](#type-nested_pair) -> [arrow](#type-arrow) -> string -> [nested_pair](#type-nested_pair) array +> +> [labeled_higher_order](#type-labeled_higher_order) -> +> [ `Bar | `Baz of +> [triple](#type-triple) ] -> +> [pair](#type-pair) +> -> +> [labeled](#type-labeled) -> +> [higher_order](#type-higher_order) +> -> +> ( string -> int ) -> +> (int * float * char * string * char * unit) +> option -> +> [nested_pair](#type-nested_pair) -> +> [arrow](#type-arrow) +> -> +> string -> +> [nested_pair](#type-nested_pair) array @@ -104,7 +120,7 @@ Some _documentation_ . -###### type variant = +###### type variant = @@ -142,7 +158,7 @@ _bar_ -###### type _ gadt = +###### type _ gadt = @@ -158,7 +174,7 @@ _bar_ -###### type degenerate_gadt = +###### type degenerate_gadt = @@ -166,7 +182,7 @@ _bar_ -###### type private_variant = private +###### type private_variant = private @@ -204,49 +220,49 @@ _bar_ -###### type polymorphic_variant = [ +###### type polymorphic_variant = [ -######    `| ` `` `A `` +######    `| ``` `A `` -######    `| ` `` int of `B `` +######    `| ``` int of `B `` -######    `| ` `` unit* int of `C `` +######    `| ``` unit* int of `C `` -######    `| ` `` `D `` +######    `| ``` `D `` -] + ] -###### type polymorphic_variant_extension = [ +###### type polymorphic_variant_extension = [ -######    `| ` [polymorphic_variant](#type-polymorphic_variant) +######    `| `[polymorphic_variant](#type-polymorphic_variant) -######    `| ` `` `E `` +######    `| ``` `E `` -] + ] -###### type nested_polymorphic_variant = [ +###### type nested_polymorphic_variant = [ -######    `| ` `` [ `B | `C ] of `A `` +######    `| ``` [ `B | `C ] of `A `` -] + ] @@ -254,13 +270,13 @@ _bar_ -###### and private_extenion = private [> +###### and private_extenion = private [> -######    `| ` [polymorphic_variant](#type-polymorphic_variant) +######    `| `[polymorphic_variant](#type-polymorphic_variant) -] + ] @@ -276,13 +292,15 @@ _bar_ ###### type module_ = -> ( module [X](Type.module-type-X.md) ) +> (module [X](Type.module-type-X.md)) ###### type module_substitution = -> ( module [X](Type.module-type-X.md) with type [t](Type.module-type-X.md#type-t) = int and type [u](Type.module-type-X.md#type-u) = unit ) +> (module [X](Type.module-type-X.md) with type +> [t](Type.module-type-X.md#type-t) = int and type +> [u](Type.module-type-X.md#type-u) = unit) @@ -306,7 +324,7 @@ _bar_ ###### type using_binary = -> ( int , int ) [binary](#type-binary) +> ( int, int ) [binary](#type-binary) @@ -334,7 +352,7 @@ _bar_ ###### type 'a any_variant = -> 'a constraint 'a = [> ] +> 'a constraint 'a = [> ] @@ -358,7 +376,7 @@ _bar_ ###### type 'a lower_object = -> 'a constraint 'a = < a : int ; b : int .. > +> 'a constraint 'a = < a : int ; b : int.. > @@ -376,7 +394,7 @@ _bar_ ###### type as_ = -> int as ' a * 'a +> int as 'a * 'a @@ -386,23 +404,23 @@ _bar_ -###### type [extensible](#type-extensible) += +###### type [extensible](#type-extensible) += ######    | Extension -Documentation for [`Extension`](#extension-Extension) . +Documentation for [`Extension`](#extension-Extension). ######    | Another_extension -Documentation for [`Another_extension`](#extension-Another_extension) . +Documentation for [`Another_extension`](#extension-Another_extension). -###### type mutually = +###### type mutually = @@ -410,7 +428,7 @@ Documentation for [`Another_extension`](#extension-Another_extension) . -###### and recursive = +###### and recursive = diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index d5c7b0f803..88fbb1206b 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -4,7 +4,8 @@ mld --- -This is an `.mld` file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. +This is an `.mld` file. It doesn't have an auto-generated title, like modules +and other pages generated fully by odoc do. It will have a TOC generated from section headings. From 5726a9ba6548005c7f07e477c434c81bf966e351 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 7 Feb 2022 18:07:53 +0100 Subject: [PATCH 28/38] Remove inlines concatenation with spaces --- src/markdown/generator.ml | 16 ++++----- src/markdown/markup.ml | 11 ++---- src/markdown/markup.mli | 8 ++--- test/generators/markdown/Markup.md | 28 +++++++-------- .../Ocamlary.ModuleWithSignatureAlias.md | 2 +- test/generators/markdown/Ocamlary.md | 36 +++++++++---------- 6 files changed, 45 insertions(+), 56 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index ef5180211b..8ed32ba978 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -34,9 +34,8 @@ let style (style : style) = | `Superscript -> superscript | `Subscript -> subscript -(** Fold inlines using [join]. *) let fold_inlines f elts : inlines = - List.fold_left (fun acc elt -> join acc (f elt)) noop elts + List.fold_left (fun acc elt -> acc ++ f elt) noop elts let fold_blocks f elts : blocks = List.fold_left (fun acc elt -> acc +++ f elt) noop_block elts @@ -185,9 +184,10 @@ and description_one args { Description.key; definition; _ } = let def = match definition with | [] -> noop - | h :: _ -> ( match h.desc with Inline i -> inline i args | _ -> noop) + | h :: _ -> ( + match h.desc with Inline i -> space ++ inline i args | _ -> noop) in - paragraph (join (text "@") (join key (text ":")) ++ def) + paragraph (text "@" ++ key ++ def) (** Generates the 6-heading used to differentiate items. Non-breaking spaces are inserted just before the text, to simulate indentation depending on @@ -196,12 +196,12 @@ and description_one args { Description.key; definition; _ } = ######Text v} *) let item_heading nesting_level content = - let pre_hash = text (String.make 6 '#') - and pre_nbsp = + let pre_nbsp = if nesting_level = 0 then noop - else text (string_repeat (nesting_level * 2) "\u{A0}") + else text (string_repeat (nesting_level * 2) "\u{A0}") ++ text " " + (* Use literal spaces to avoid breaking. *) in - paragraph (pre_hash ++ pre_nbsp ++ content) + heading 6 (pre_nbsp ++ content) let take_code l = let c, _, rest = diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index c775c2503c..c9b8e2561f 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -5,9 +5,7 @@ type inlines = | String of string - | ConcatI of inlines * inlines | Join of inlines * inlines - (** [Join] constructor is for joining [inlines] without spaces between them. *) | Link of string * inlines | Anchor of string | Linebreak @@ -31,10 +29,7 @@ let unordered_list bs = List (Unordered, bs) (* Make sure to never leave a [Noop] in the result, which would cause unwanted spaces. *) -let ( ++ ) left right = - match (left, right) with Noop, x | x, Noop -> x | _ -> ConcatI (left, right) - -let join left right = Join (left, right) +let ( ++ ) left right = Join (left, right) let blocks above below = ConcatB (above, below) @@ -82,7 +77,7 @@ let noop_block = Block Noop let heading level i = let make_hashes n = String.make n '#' in let hashes = make_hashes level in - Block (String hashes ++ i) + Block (String hashes ++ String " " ++ i) (** [split_on_char] is not available on [< 4.04]. *) let rec iter_lines f s i = @@ -108,8 +103,6 @@ let pp_list_item fmt list_type (b : blocks) n pp_blocks = let rec pp_inlines fmt i = match i with | String s -> Format.fprintf fmt "%s" s - | ConcatI (left, right) -> - Format.fprintf fmt "%a@ %a" pp_inlines left pp_inlines right | Join (left, right) -> Format.fprintf fmt "%a%a" pp_inlines left pp_inlines right | Link (href, i) -> Format.fprintf fmt "[%a](%s)" pp_inlines i href diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index bc93f1ac57..4fefb64667 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -4,13 +4,9 @@ (** {2 Inline elements} *) type inlines -(** Inlines elements are rendered one after the other, separated by spaces. *) val ( ++ ) : inlines -> inlines -> inlines -(** Combine inlines, render a breakable space between two inlines. *) - -val join : inlines -> inlines -> inlines -(** Join inlines without spaces in between. *) +(** Renders two inlines one after the other. *) val text : string -> inlines (** An arbitrary string. *) @@ -20,7 +16,7 @@ val space : inlines val line_break : inlines val noop : inlines -(** Nothing. Isn't separated by spaces: [noop ++ x = x ++ noop = x]. *) +(** Nothing. *) val bold : inlines -> inlines diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 86c145f7ac..0e29849830 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -175,37 +175,37 @@ into sentences. # Modules -@[`X`](Markup.X.md): +@[`X`](Markup.X.md) -@[`X`](Markup.X.md): +@[`X`](Markup.X.md) -@[`Y`](Markup.Y.md): +@[`Y`](Markup.Y.md) # Tags Each comment can end with zero or more tags. Here are some examples: -@author: antron +@author antron -@deprecated: +@deprecated -@parameter foo: +@parameter foo -@raises Failure: +@raises Failure -@returns: +@returns -@see [#](#): +@see [#](#) -@see `foo.ml`: +@see `foo.ml` -@see Foo: +@see Foo -@since: 0 +@since 0 -@before 1.0: +@before 1.0 -@version: -1 +@version -1 diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md index 3cb01089e8..ae682f4410 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignatureAlias.md @@ -6,4 +6,4 @@ Module `Ocamlary.ModuleWithSignatureAlias` A plain module with an alias signature -@deprecated: +@deprecated diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 96d3fbe428..64abf0d812 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -48,7 +48,7 @@ A numbered list: David Sheets is the author. -@author: David Sheets +@author David Sheets You may find more information about this HTML documentation renderer at [github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary). @@ -67,9 +67,9 @@ Here is some raw LaTeX: $e^{i\pi} = -1$ Here is an index table of `Empty` modules: -@[`Empty`](Ocamlary.Empty.md): A plain, empty module +@[`Empty`](Ocamlary.Empty.md) A plain, empty module -@[`EmptyAlias`](Ocamlary.Empty.md): A plain module alias of `Empty` +@[`EmptyAlias`](Ocamlary.Empty.md) A plain module alias of `Empty` Odoc doesn't support `{!indexlist}`. @@ -249,9 +249,9 @@ Unary exception constructor over binary tuple This is `a_function` with param and return type. -@parameter x: +@parameter x -@returns: +@returns @@ -273,7 +273,7 @@ This is `a_function` with param and return type. > unit -> unit -@raises Not_found: +@raises Not_found @@ -281,7 +281,7 @@ This is `a_function` with param and return type. > string -@see [http://ocaml.org/](http://ocaml.org/): +@see [http://ocaml.org/](http://ocaml.org/) @@ -289,7 +289,7 @@ This is `a_function` with param and return type. > string -@see `some_file`: +@see `some_file` @@ -297,7 +297,7 @@ This is `a_function` with param and return type. > string -@see some_doc: +@see some_doc @@ -307,7 +307,7 @@ This is `a_function` with param and return type. This value was introduced in the Mesozoic era. -@since: mesozoic +@since mesozoic @@ -317,11 +317,11 @@ This value was introduced in the Mesozoic era. This value has had changes in 1.0.0, 1.1.0, and 1.2.0. -@before 1.0.0: +@before 1.0.0 -@before 1.1.0: +@before 1.1.0 -@version: 1.2.0 +@version 1.2.0 ### Some Operators @@ -1262,20 +1262,20 @@ will behave as simple references. With odoc, everything should be resolved (and linked) but only toplevel units will be documented. -@[`Dep1.X`](Ocamlary.Dep1.X.md): +@[`Dep1.X`](Ocamlary.Dep1.X.md) -@[`Ocamlary.IncludeInclude1`](Ocamlary.IncludeInclude1.md): +@[`Ocamlary.IncludeInclude1`](Ocamlary.IncludeInclude1.md) -@[`Ocamlary`](): This is an _interface_ with **all** of the _module system_ +@[`Ocamlary`]() This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: ### Weirder usages involving module types --- -@[`IncludeInclude1.IncludeInclude2_M`](Ocamlary.IncludeInclude1.IncludeInclude2_M.md): +@[`IncludeInclude1.IncludeInclude2_M`](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) -@[`Dep4.X`](Ocamlary.Dep4.X.md): +@[`Dep4.X`](Ocamlary.Dep4.X.md) # Playing with @canonical paths From b4d5f6d8348c9bcbe9776fa6f40111d288479fed Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Mon, 7 Feb 2022 18:11:13 +0100 Subject: [PATCH 29/38] document: Remove extra space after class keyword --- src/document/generator.ml | 17 ++++++++++++----- test/generators/html/Bugs_post_406.html | 4 ++-- test/generators/html/Class.html | 14 +++++++------- test/generators/html/Labels.html | 4 ++-- test/generators/html/Nested.html | 4 ++-- test/generators/html/Ocamlary-Dep1-X-Y.html | 2 +- .../html/Ocamlary-Dep1-module-type-S.html | 2 +- .../html/Ocamlary-Dep11-module-type-S.html | 2 +- test/generators/html/Ocamlary-Dep13.html | 2 +- test/generators/html/Ocamlary.html | 6 +++--- test/generators/html/Toplevel_comments.html | 6 +++--- test/generators/latex/Bugs_post_406.tex | 4 ++-- test/generators/latex/Class.tex | 14 +++++++------- test/generators/latex/Labels.tex | 4 ++-- test/generators/latex/Nested.tex | 4 ++-- test/generators/latex/Ocamlary.Dep13.tex | 2 +- test/generators/latex/Ocamlary.tex | 10 +++++----- test/generators/latex/Toplevel_comments.tex | 6 +++--- test/generators/man/Bugs_post_406.3o | 4 ++-- test/generators/man/Class.3o | 14 +++++++------- test/generators/man/Labels.3o | 4 ++-- test/generators/man/Nested.3o | 4 ++-- test/generators/man/Ocamlary.3o | 6 +++--- test/generators/man/Ocamlary.Dep1.3o | 2 +- test/generators/man/Ocamlary.Dep1.X.Y.3o | 2 +- test/generators/man/Ocamlary.Dep11.3o | 2 +- test/generators/man/Ocamlary.Dep13.3o | 2 +- test/generators/man/Toplevel_comments.3o | 6 +++--- test/generators/markdown/Bugs_post_406.md | 4 ++-- test/generators/markdown/Class.md | 14 +++++++------- test/generators/markdown/Labels.md | 4 ++-- test/generators/markdown/Nested.md | 4 ++-- test/generators/markdown/Ocamlary.Dep1.X.Y.md | 2 +- .../markdown/Ocamlary.Dep1.module-type-S.md | 2 +- .../markdown/Ocamlary.Dep11.module-type-S.md | 2 +- test/generators/markdown/Ocamlary.Dep13.md | 2 +- test/generators/markdown/Ocamlary.md | 6 +++--- test/generators/markdown/Toplevel_comments.md | 6 +++--- 38 files changed, 103 insertions(+), 96 deletions(-) diff --git a/src/document/generator.ml b/src/document/generator.ml index e4fdc41442..82b565ed03 100644 --- a/src/document/generator.ml +++ b/src/document/generator.ml @@ -1014,7 +1014,11 @@ module Make (Syntax : SYNTAX) = struct let class_ (t : Odoc_model.Lang.Class.t) = let name = Paths.Identifier.name t.id in - let params = format_params ~delim:`brackets t.params in + let params = + match t.params with + | [] -> O.noop + | params -> format_params ~delim:`brackets params ++ O.txt " " + in let virtual_ = if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop in @@ -1041,8 +1045,7 @@ module Make (Syntax : SYNTAX) = struct expansion summary in let content = - O.documentedSrc - (O.keyword "class" ++ O.txt " " ++ virtual_ ++ params ++ O.txt " ") + O.documentedSrc (O.keyword "class" ++ O.txt " " ++ virtual_ ++ params) @ cname @ cd in let attr = [ "class" ] in @@ -1052,7 +1055,11 @@ module Make (Syntax : SYNTAX) = struct let class_type (t : Odoc_model.Lang.ClassType.t) = let name = Paths.Identifier.name t.id in - let params = format_params ~delim:`brackets t.params in + let params = + match t.params with + | [] -> O.noop + | params -> format_params ~delim:`brackets params ++ O.txt " " + in let virtual_ = if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop in @@ -1074,7 +1081,7 @@ module Make (Syntax : SYNTAX) = struct let content = O.documentedSrc (O.keyword "class" ++ O.txt " " ++ O.keyword "type" ++ O.txt " " - ++ virtual_ ++ params ++ O.txt " ") + ++ virtual_ ++ params) @ cname @ expr in let attr = [ "class-type" ] in diff --git a/test/generators/html/Bugs_post_406.html b/test/generators/html/Bugs_post_406.html index 73ca532ec8..944369b336 100644 --- a/test/generators/html/Bugs_post_406.html +++ b/test/generators/html/Bugs_post_406.html @@ -20,7 +20,7 @@

Module Bugs_post_406

class - type + type let_open @@ -33,7 +33,7 @@

Module Bugs_post_406

- class + class let_open' : object ... end diff --git a/test/generators/html/Class.html b/test/generators/html/Class.html index 99af51a5bc..02dc21f3f9 100644 --- a/test/generators/html/Class.html +++ b/test/generators/html/Class.html @@ -16,7 +16,7 @@

Module Class

class - type + type empty = object ... end @@ -29,7 +29,7 @@

Module Class

class - type + type mutually = object ... @@ -43,7 +43,7 @@

Module Class

class - type + type recursive = object ... @@ -55,7 +55,7 @@

Module Class

- class + class mutually' : mutually @@ -64,7 +64,7 @@

Module Class

- class + class recursive' : recursive @@ -76,7 +76,7 @@

Module Class

class type virtual - + empty_virtual @@ -91,7 +91,7 @@

Module Class

class - virtual + virtual empty_virtual' : empty diff --git a/test/generators/html/Labels.html b/test/generators/html/Labels.html index 61cec92c38..4a875e15a6 100644 --- a/test/generators/html/Labels.html +++ b/test/generators/html/Labels.html @@ -73,7 +73,7 @@

Attached to nothing

- class + class c : object ... end @@ -86,7 +86,7 @@

Attached to nothing

class - type + type cs = object ... end diff --git a/test/generators/html/Nested.html b/test/generators/html/Nested.html index dd019b5c53..35239a4f5d 100644 --- a/test/generators/html/Nested.html +++ b/test/generators/html/Nested.html @@ -69,7 +69,7 @@

Module type class - virtual + virtual z : object ... end @@ -82,7 +82,7 @@

Module type class - virtual + virtual inherits : object ... end diff --git a/test/generators/html/Ocamlary-Dep1-X-Y.html b/test/generators/html/Ocamlary-Dep1-X-Y.html index d1e97e124a..2624000651 100644 --- a/test/generators/html/Ocamlary-Dep1-X-Y.html +++ b/test/generators/html/Ocamlary-Dep1-X-Y.html @@ -19,7 +19,7 @@
- class + class c : object ... end diff --git a/test/generators/html/Ocamlary-Dep1-module-type-S.html b/test/generators/html/Ocamlary-Dep1-module-type-S.html index 5e4047f6e4..4b59c4d052 100644 --- a/test/generators/html/Ocamlary-Dep1-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep1-module-type-S.html @@ -19,7 +19,7 @@

Module type Dep1.S

- class + class c : object ... end diff --git a/test/generators/html/Ocamlary-Dep11-module-type-S.html b/test/generators/html/Ocamlary-Dep11-module-type-S.html index 207c445c81..f7eb9acc95 100644 --- a/test/generators/html/Ocamlary-Dep11-module-type-S.html +++ b/test/generators/html/Ocamlary-Dep11-module-type-S.html @@ -19,7 +19,7 @@

Module type Dep11.S

- class + class c : object ... end diff --git a/test/generators/html/Ocamlary-Dep13.html b/test/generators/html/Ocamlary-Dep13.html index bd42910855..d9e4b345db 100644 --- a/test/generators/html/Ocamlary-Dep13.html +++ b/test/generators/html/Ocamlary-Dep13.html @@ -18,7 +18,7 @@

Module Ocamlary.Dep13

- class + class c : object ... end diff --git a/test/generators/html/Ocamlary.html b/test/generators/html/Ocamlary.html index 45c4028f81..ca0cab730b 100644 --- a/test/generators/html/Ocamlary.html +++ b/test/generators/html/Ocamlary.html @@ -2111,7 +2111,7 @@

- class + class empty_class : object ... end @@ -2122,7 +2122,7 @@

- class + class one_method_class @@ -2135,7 +2135,7 @@

- class + class two_method_class diff --git a/test/generators/html/Toplevel_comments.html b/test/generators/html/Toplevel_comments.html index 99746fe19a..b6a3241139 100644 --- a/test/generators/html/Toplevel_comments.html +++ b/test/generators/html/Toplevel_comments.html @@ -148,7 +148,7 @@

Module Toplevel_comments

- class + class c1 : int -> object ... @@ -162,7 +162,7 @@

Module Toplevel_comments

class - type + type ct = object ... @@ -174,7 +174,7 @@

Module Toplevel_comments

- class + class c2 : ct diff --git a/test/generators/latex/Bugs_post_406.tex b/test/generators/latex/Bugs_post_406.tex index 607db98fb1..7dd8c6a538 100644 --- a/test/generators/latex/Bugs_post_406.tex +++ b/test/generators/latex/Bugs_post_406.tex @@ -1,8 +1,8 @@ \section{Module \ocamlinlinecode{Bugs\_\allowbreak{}post\_\allowbreak{}406}}\label{module-Bugs+u+post+u+406}% Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 -\label{module-Bugs+u+post+u+406-class-type-let+u+open}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Bugs+u+post+u+406-class-type-let+u+open]{\ocamlinlinecode{let\_\allowbreak{}open}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{module-Bugs+u+post+u+406-class-type-let+u+open}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Bugs+u+post+u+406-class-type-let+u+open]{\ocamlinlinecode{let\_\allowbreak{}open}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Bugs+u+post+u+406-class-let+u+open'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Bugs+u+post+u+406-class-let+u+open']{\ocamlinlinecode{let\_\allowbreak{}open'}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Bugs+u+post+u+406-class-let+u+open'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Bugs+u+post+u+406-class-let+u+open']{\ocamlinlinecode{let\_\allowbreak{}open'}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Bugs_post_406.let_open'.tex} diff --git a/test/generators/latex/Class.tex b/test/generators/latex/Class.tex index 672e906372..275fecb592 100644 --- a/test/generators/latex/Class.tex +++ b/test/generators/latex/Class.tex @@ -1,15 +1,15 @@ \section{Module \ocamlinlinecode{Class}}\label{module-Class}% -\label{module-Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{module-Class-class-type-empty}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{module-Class-class-type-mutually}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{module-Class-class-type-recursive}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\ -\label{module-Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\ -\label{module-Class-class-type-empty+u+virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[module-Class-class-type-empty+u+virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{module-Class-class-mutually'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class-class-mutually']{\ocamlinlinecode{mutually'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-mutually]{\ocamlinlinecode{mutually}}}\\ +\label{module-Class-class-recursive'}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Class-class-recursive']{\ocamlinlinecode{recursive'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-recursive]{\ocamlinlinecode{recursive}}}\\ +\label{module-Class-class-type-empty+u+virtual}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \ocamltag{keyword}{virtual} \hyperref[module-Class-class-type-empty+u+virtual]{\ocamlinlinecode{empty\_\allowbreak{}virtual}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Class-class-empty+u+virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Class-class-empty+u+virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\\ +\label{module-Class-class-empty+u+virtual'}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Class-class-empty+u+virtual']{\ocamlinlinecode{empty\_\allowbreak{}virtual'}}}\ocamlcodefragment{ : \hyperref[module-Class-class-type-empty]{\ocamlinlinecode{empty}}}\\ \label{module-Class-class-type-polymorphic}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} 'a \hyperref[module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \label{module-Class-class-polymorphic'}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[module-Class-class-polymorphic']{\ocamlinlinecode{polymorphic'}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \hyperref[module-Class-class-type-polymorphic]{\ocamlinlinecode{polymorphic}}}\\ diff --git a/test/generators/latex/Labels.tex b/test/generators/latex/Labels.tex index c1d81a3cf5..8f2091541c 100644 --- a/test/generators/latex/Labels.tex +++ b/test/generators/latex/Labels.tex @@ -13,8 +13,8 @@ \subsection{Attached to nothing\label{L2}}% \label{module-Labels-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Labels-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\subsubsection{Attached to module type\label{L6}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Labels-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Labels-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L8}}% +\label{module-Labels-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Labels-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Labels-class-type-cs}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Labels-class-type-cs]{\ocamlinlinecode{cs}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\subsubsection{Attached to class type\label{L8}}% \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \label{module-Labels-exception-E}\ocamlcodefragment{\ocamltag{keyword}{exception} \ocamltag{exception}{E}}\begin{ocamlindent}Attached to exception\end{ocamlindent}% diff --git a/test/generators/latex/Nested.tex b/test/generators/latex/Nested.tex index 417935cab5..d862d10875 100644 --- a/test/generators/latex/Nested.tex +++ b/test/generators/latex/Nested.tex @@ -25,9 +25,9 @@ \subsection{Functor\label{functor}}% \label{module-Nested-module-F}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Nested-module-F]{\ocamlinlinecode{F}}}\ocamlcodefragment{ (\hyperref[module-Nested-module-F-argument-1-Arg1]{\ocamlinlinecode{Arg1}} : \hyperref[module-Nested-module-type-Y]{\ocamlinlinecode{Y}}) (\hyperref[module-Nested-module-F-argument-2-Arg2]{\ocamlinlinecode{Arg2}} : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}) : \ocamltag{keyword}{sig} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is a functor F.\end{ocamlindent}% \medbreak \subsection{Class\label{class}}% -\label{module-Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}% +\label{module-Nested-class-z}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Nested-class-z]{\ocamlinlinecode{z}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}This is class z.\end{ocamlindent}% \medbreak -\label{module-Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Nested-class-inherits}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{virtual} \hyperref[module-Nested-class-inherits]{\ocamlinlinecode{inherits}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Nested.F.tex} \input{Nested.z.tex} diff --git a/test/generators/latex/Ocamlary.Dep13.tex b/test/generators/latex/Ocamlary.Dep13.tex index 1cb1cf36d9..e7768b1019 100644 --- a/test/generators/latex/Ocamlary.Dep13.tex +++ b/test/generators/latex/Ocamlary.Dep13.tex @@ -1,4 +1,4 @@ \section{Module \ocamlinlinecode{Ocamlary.\allowbreak{}Dep13}}\label{module-Ocamlary-module-Dep13}% -\label{module-Ocamlary-module-Dep13-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep13-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Ocamlary-module-Dep13-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep13-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \input{Ocamlary.Dep13.c.tex} diff --git a/test/generators/latex/Ocamlary.tex b/test/generators/latex/Ocamlary.tex index 01757c4498..a7da6cba59 100644 --- a/test/generators/latex/Ocamlary.tex +++ b/test/generators/latex/Ocamlary.tex @@ -602,13 +602,13 @@ \subsubsection{Advanced Type Stuff\label{advanced-type-stuff}}% \medbreak \label{module-Ocamlary-type-my+u+mod}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}mod = (\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-type-COLLECTION]{\ocamlinlinecode{COLLECTION}})}\begin{ocamlindent}A brown paper package tied up with string\end{ocamlindent}% \medbreak -\label{module-Ocamlary-class-empty+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-empty+u+class]{\ocamlinlinecode{empty\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-class-one+u+method+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-one+u+method+u+class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-class-two+u+method+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-two+u+method+u+class]{\ocamlinlinecode{two\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Ocamlary-class-empty+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-empty+u+class]{\ocamlinlinecode{empty\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Ocamlary-class-one+u+method+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-one+u+method+u+class]{\ocamlinlinecode{one\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ +\label{module-Ocamlary-class-two+u+method+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-class-two+u+method+u+class]{\ocamlinlinecode{two\_\allowbreak{}method\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \label{module-Ocamlary-class-param+u+class}\ocamlcodefragment{\ocamltag{keyword}{class} 'a \hyperref[module-Ocamlary-class-param+u+class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\ocamlcodefragment{ : \ocamltag{type-var}{'a} \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\\ \label{module-Ocamlary-type-my+u+unit+u+object}\ocamlcodefragment{\ocamltag{keyword}{type} my\_\allowbreak{}unit\_\allowbreak{}object = unit \hyperref[module-Ocamlary-class-param+u+class]{\ocamlinlinecode{param\_\allowbreak{}class}}}\\ \label{module-Ocamlary-type-my+u+unit+u+class}\ocamlcodefragment{\ocamltag{keyword}{type} 'a my\_\allowbreak{}unit\_\allowbreak{}class = unit \hyperref[xref-unresolved]{\ocamlinlinecode{param\_\allowbreak{}class}} \ocamltag{keyword}{as} 'a}\\ -\label{module-Ocamlary-module-Dep1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep1]{\ocamlinlinecode{Dep1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep1-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep1-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ +\label{module-Ocamlary-module-Dep1}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep1]{\ocamlinlinecode{Dep1}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep1-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep1-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep1-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% @@ -662,7 +662,7 @@ \subsubsection{Advanced Type Stuff\label{advanced-type-stuff}}% \label{module-Ocamlary-module-type-Dep10}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-type-Dep10]{\ocamlinlinecode{Dep10}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-type-Dep10-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t = int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ -\label{module-Ocamlary-module-Dep11}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep11]{\ocamlinlinecode{Dep11}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep11-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep11-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ +\label{module-Ocamlary-module-Dep11}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Ocamlary-module-Dep11]{\ocamlinlinecode{Dep11}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S}\ocamlcodefragment{\ocamltag{keyword}{module} \ocamltag{keyword}{type} \hyperref[module-Ocamlary-module-Dep11-module-type-S]{\ocamlinlinecode{S}}}\ocamlcodefragment{ = \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S-class-c}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Ocamlary-module-Dep11-module-type-S-class-c]{\ocamlinlinecode{c}}}\ocamlcodefragment{ : \ocamltag{keyword}{object}}\begin{ocamlindent}\label{module-Ocamlary-module-Dep11-module-type-S-class-c-method-m}\ocamlcodefragment{\ocamltag{keyword}{method} m : int}\\ \end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\\ \end{ocamlindent}% diff --git a/test/generators/latex/Toplevel_comments.tex b/test/generators/latex/Toplevel_comments.tex index 83d43a0b18..7206802b48 100644 --- a/test/generators/latex/Toplevel_comments.tex +++ b/test/generators/latex/Toplevel_comments.tex @@ -32,12 +32,12 @@ \section{Module \ocamlinlinecode{Toplevel\_\allowbreak{}comments}}\label{module- \medbreak \label{module-Toplevel+u+comments-module-Alias}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel+u+comments-module-Alias]{\ocamlinlinecode{Alias}}}\ocamlcodefragment{ : \hyperref[module-Toplevel+u+comments-module-type-T]{\ocamlinlinecode{T}}}\begin{ocamlindent}Doc of \ocamlinlinecode{Alias}.\end{ocamlindent}% \medbreak -\label{module-Toplevel+u+comments-class-c1}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Toplevel+u+comments-class-c1]{\ocamlinlinecode{c1}}}\ocamlcodefragment{ : int \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{c1}, part 1.\end{ocamlindent}% +\label{module-Toplevel+u+comments-class-c1}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Toplevel+u+comments-class-c1]{\ocamlinlinecode{c1}}}\ocamlcodefragment{ : int \ocamltag{arrow}{$\rightarrow$} \ocamltag{keyword}{object} .\allowbreak{}.\allowbreak{}.\allowbreak{} \ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{c1}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel+u+comments-class-type-ct}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Toplevel+u+comments-class-type-ct]{\ocamlinlinecode{ct}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% +\label{module-Toplevel+u+comments-class-type-ct}\ocamlcodefragment{\ocamltag{keyword}{class} \ocamltag{keyword}{type} \hyperref[module-Toplevel+u+comments-class-type-ct]{\ocamlinlinecode{ct}}}\ocamlcodefragment{ = \ocamltag{keyword}{object}}\begin{ocamlindent}\end{ocamlindent}% \ocamlcodefragment{\ocamltag{keyword}{end}}\begin{ocamlindent}Doc of \ocamlinlinecode{ct}, part 1.\end{ocamlindent}% \medbreak -\label{module-Toplevel+u+comments-class-c2}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Toplevel+u+comments-class-c2]{\ocamlinlinecode{c2}}}\ocamlcodefragment{ : \hyperref[module-Toplevel+u+comments-class-type-ct]{\ocamlinlinecode{ct}}}\begin{ocamlindent}Doc of \ocamlinlinecode{c2}.\end{ocamlindent}% +\label{module-Toplevel+u+comments-class-c2}\ocamlcodefragment{\ocamltag{keyword}{class} \hyperref[module-Toplevel+u+comments-class-c2]{\ocamlinlinecode{c2}}}\ocamlcodefragment{ : \hyperref[module-Toplevel+u+comments-class-type-ct]{\ocamlinlinecode{ct}}}\begin{ocamlindent}Doc of \ocamlinlinecode{c2}.\end{ocamlindent}% \medbreak \label{module-Toplevel+u+comments-module-Ref+u+in+u+synopsis}\ocamlcodefragment{\ocamltag{keyword}{module} \hyperref[module-Toplevel+u+comments-module-Ref+u+in+u+synopsis]{\ocamlinlinecode{Ref\_\allowbreak{}in\_\allowbreak{}synopsis}}}\ocamlcodefragment{ : \ocamltag{keyword}{sig}}\begin{ocamlindent}\label{module-Toplevel+u+comments-module-Ref+u+in+u+synopsis-type-t}\ocamlcodefragment{\ocamltag{keyword}{type} t}\\ \end{ocamlindent}% diff --git a/test/generators/man/Bugs_post_406.3o b/test/generators/man/Bugs_post_406.3o index 4f2dd8ad96..c613867d12 100644 --- a/test/generators/man/Bugs_post_406.3o +++ b/test/generators/man/Bugs_post_406.3o @@ -14,6 +14,6 @@ Let-open in class types, https://github\.com/ocaml/odoc/issues/543 This was adde .SH Documentation .sp .nf -\f[CB]class\fR \f[CB]type\fR let_open = \f[CB]object\fR \f[CB]end\fR +\f[CB]class\fR \f[CB]type\fR let_open = \f[CB]object\fR \f[CB]end\fR .sp -\f[CB]class\fR let_open' : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR let_open' : \f[CB]object\fR \.\.\. \f[CB]end\fR diff --git a/test/generators/man/Class.3o b/test/generators/man/Class.3o index ecf092eda9..68773116dd 100644 --- a/test/generators/man/Class.3o +++ b/test/generators/man/Class.3o @@ -11,19 +11,19 @@ Class .SH Documentation .sp .nf -\f[CB]class\fR \f[CB]type\fR empty = \f[CB]object\fR \f[CB]end\fR +\f[CB]class\fR \f[CB]type\fR empty = \f[CB]object\fR \f[CB]end\fR .sp -\f[CB]class\fR \f[CB]type\fR mutually = \f[CB]object\fR \f[CB]end\fR +\f[CB]class\fR \f[CB]type\fR mutually = \f[CB]object\fR \f[CB]end\fR .sp -\f[CB]class\fR \f[CB]type\fR recursive = \f[CB]object\fR \f[CB]end\fR +\f[CB]class\fR \f[CB]type\fR recursive = \f[CB]object\fR \f[CB]end\fR .sp -\f[CB]class\fR mutually' : mutually +\f[CB]class\fR mutually' : mutually .sp -\f[CB]class\fR recursive' : recursive +\f[CB]class\fR recursive' : recursive .sp -\f[CB]class\fR \f[CB]type\fR \f[CB]virtual\fR empty_virtual = \f[CB]object\fR \f[CB]end\fR +\f[CB]class\fR \f[CB]type\fR \f[CB]virtual\fR empty_virtual = \f[CB]object\fR \f[CB]end\fR .sp -\f[CB]class\fR \f[CB]virtual\fR empty_virtual' : empty +\f[CB]class\fR \f[CB]virtual\fR empty_virtual' : empty .sp \f[CB]class\fR \f[CB]type\fR 'a polymorphic = \f[CB]object\fR \f[CB]end\fR .sp diff --git a/test/generators/man/Labels.3o b/test/generators/man/Labels.3o index da49e51e7c..cbe6094f0e 100644 --- a/test/generators/man/Labels.3o +++ b/test/generators/man/Labels.3o @@ -55,9 +55,9 @@ Attached to external .br \f[CB]end\fR .sp -\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR .sp -\f[CB]class\fR \f[CB]type\fR cs = \f[CB]object\fR +\f[CB]class\fR \f[CB]type\fR cs = \f[CB]object\fR .br .ti +2 .sp diff --git a/test/generators/man/Nested.3o b/test/generators/man/Nested.3o index 244545e49f..07530adcfc 100644 --- a/test/generators/man/Nested.3o +++ b/test/generators/man/Nested.3o @@ -79,11 +79,11 @@ This is a functor F\. \fB4 Class\fR .in .sp -\f[CB]class\fR \f[CB]virtual\fR z : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR \f[CB]virtual\fR z : \f[CB]object\fR \.\.\. \f[CB]end\fR .fi .br .ti +2 This is class z\. .nf .sp -\f[CB]class\fR \f[CB]virtual\fR inherits : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR \f[CB]virtual\fR inherits : \f[CB]object\fR \.\.\. \f[CB]end\fR diff --git a/test/generators/man/Ocamlary.3o b/test/generators/man/Ocamlary.3o index 6b6791d3af..3b6586f04b 100644 --- a/test/generators/man/Ocamlary.3o +++ b/test/generators/man/Ocamlary.3o @@ -1577,11 +1577,11 @@ Rotate keys on my mark\.\.\. A brown paper package tied up with string .nf .sp -\f[CB]class\fR empty_class : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR empty_class : \f[CB]object\fR \.\.\. \f[CB]end\fR .sp -\f[CB]class\fR one_method_class : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR one_method_class : \f[CB]object\fR \.\.\. \f[CB]end\fR .sp -\f[CB]class\fR two_method_class : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR two_method_class : \f[CB]object\fR \.\.\. \f[CB]end\fR .sp \f[CB]class\fR 'a param_class : \f[CB]'a\fR \f[CB]\->\fR \f[CB]object\fR \.\.\. \f[CB]end\fR .sp diff --git a/test/generators/man/Ocamlary.Dep1.3o b/test/generators/man/Ocamlary.Dep1.3o index 4a2879ef32..282ffbb157 100644 --- a/test/generators/man/Ocamlary.Dep1.3o +++ b/test/generators/man/Ocamlary.Dep1.3o @@ -14,7 +14,7 @@ Ocamlary\.Dep1 \f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR .br .ti +2 -\f[CB]class\fR c : \f[CB]object\fR +\f[CB]class\fR c : \f[CB]object\fR .br .ti +4 \f[CB]method\fR m : int diff --git a/test/generators/man/Ocamlary.Dep1.X.Y.3o b/test/generators/man/Ocamlary.Dep1.X.Y.3o index 5956cfd984..19b936e9b5 100644 --- a/test/generators/man/Ocamlary.Dep1.X.Y.3o +++ b/test/generators/man/Ocamlary.Dep1.X.Y.3o @@ -11,4 +11,4 @@ Ocamlary\.Dep1\.X\.Y .SH Documentation .sp .nf -\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR diff --git a/test/generators/man/Ocamlary.Dep11.3o b/test/generators/man/Ocamlary.Dep11.3o index 98c7cd0633..5b348fdf17 100644 --- a/test/generators/man/Ocamlary.Dep11.3o +++ b/test/generators/man/Ocamlary.Dep11.3o @@ -14,7 +14,7 @@ Ocamlary\.Dep11 \f[CB]module\fR \f[CB]type\fR S = \f[CB]sig\fR .br .ti +2 -\f[CB]class\fR c : \f[CB]object\fR +\f[CB]class\fR c : \f[CB]object\fR .br .ti +4 \f[CB]method\fR m : int diff --git a/test/generators/man/Ocamlary.Dep13.3o b/test/generators/man/Ocamlary.Dep13.3o index 6525039d68..52b178ade0 100644 --- a/test/generators/man/Ocamlary.Dep13.3o +++ b/test/generators/man/Ocamlary.Dep13.3o @@ -11,4 +11,4 @@ Ocamlary\.Dep13 .SH Documentation .sp .nf -\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR c : \f[CB]object\fR \.\.\. \f[CB]end\fR diff --git a/test/generators/man/Toplevel_comments.3o b/test/generators/man/Toplevel_comments.3o index 8241e17abf..1d9b3ffe5f 100644 --- a/test/generators/man/Toplevel_comments.3o +++ b/test/generators/man/Toplevel_comments.3o @@ -92,21 +92,21 @@ Doc of M'', part 1\. Doc of Alias\. .nf .sp -\f[CB]class\fR c1 : int \f[CB]\->\fR \f[CB]object\fR \.\.\. \f[CB]end\fR +\f[CB]class\fR c1 : int \f[CB]\->\fR \f[CB]object\fR \.\.\. \f[CB]end\fR .fi .br .ti +2 Doc of c1, part 1\. .nf .sp -\f[CB]class\fR \f[CB]type\fR ct = \f[CB]object\fR \f[CB]end\fR +\f[CB]class\fR \f[CB]type\fR ct = \f[CB]object\fR \f[CB]end\fR .fi .br .ti +2 Doc of ct, part 1\. .nf .sp -\f[CB]class\fR c2 : ct +\f[CB]class\fR c2 : ct .fi .br .ti +2 diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index df49dd87b4..9245984a08 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -7,8 +7,8 @@ added to the language in 4.06 -###### class type [let_open](Bugs_post_406.class-type-let_open.md) +###### class type [let_open](Bugs_post_406.class-type-let_open.md) -###### class [let_open'](Bugs_post_406.let_open'.md) +###### class [let_open'](Bugs_post_406.let_open'.md) diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md index a52e6eb12e..e1d8761c53 100644 --- a/test/generators/markdown/Class.md +++ b/test/generators/markdown/Class.md @@ -4,31 +4,31 @@ Module `Class` -###### class type [empty](Class.class-type-empty.md) +###### class type [empty](Class.class-type-empty.md) -###### class type [mutually](Class.class-type-mutually.md) +###### class type [mutually](Class.class-type-mutually.md) -###### class type [recursive](Class.class-type-recursive.md) +###### class type [recursive](Class.class-type-recursive.md) -###### class [mutually'](Class.mutually'.md) +###### class [mutually'](Class.mutually'.md) -###### class [recursive'](Class.recursive'.md) +###### class [recursive'](Class.recursive'.md) -###### class type virtual [empty_virtual](Class.class-type-empty_virtual.md) +###### class type virtual [empty_virtual](Class.class-type-empty_virtual.md) -###### class virtual [empty_virtual'](Class.empty_virtual'.md) +###### class virtual [empty_virtual'](Class.empty_virtual'.md) diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index d6ddfcd5fc..1ae51b6212 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -38,11 +38,11 @@ Attached to external -###### class [c](Labels.c.md) +###### class [c](Labels.c.md) -###### class type [cs](Labels.class-type-cs.md) +###### class type [cs](Labels.class-type-cs.md) diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md index 6eccd935f9..a42a9b76bf 100644 --- a/test/generators/markdown/Nested.md +++ b/test/generators/markdown/Nested.md @@ -32,10 +32,10 @@ This is a functor F. -###### class virtual [z](Nested.z.md) +###### class virtual [z](Nested.z.md) This is class z. -###### class virtual [inherits](Nested.inherits.md) +###### class virtual [inherits](Nested.inherits.md) diff --git a/test/generators/markdown/Ocamlary.Dep1.X.Y.md b/test/generators/markdown/Ocamlary.Dep1.X.Y.md index 3c5db40a7a..af01294c8d 100644 --- a/test/generators/markdown/Ocamlary.Dep1.X.Y.md +++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md @@ -10,4 +10,4 @@ Module `X.Y` -###### class [c](Ocamlary.Dep1.X.Y.c.md) +###### class [c](Ocamlary.Dep1.X.Y.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md index 4bf6502812..c476643fe3 100644 --- a/test/generators/markdown/Ocamlary.Dep1.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep1.S` -###### class [c](Ocamlary.Dep1.module-type-S.c.md) +###### class [c](Ocamlary.Dep1.module-type-S.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md index 4dceb4a03b..4bfd93a3c3 100644 --- a/test/generators/markdown/Ocamlary.Dep11.module-type-S.md +++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md @@ -8,4 +8,4 @@ Module type `Dep11.S` -###### class [c](Ocamlary.Dep11.module-type-S.c.md) +###### class [c](Ocamlary.Dep11.module-type-S.c.md) diff --git a/test/generators/markdown/Ocamlary.Dep13.md b/test/generators/markdown/Ocamlary.Dep13.md index 4c3ac1093e..9aae84433f 100644 --- a/test/generators/markdown/Ocamlary.Dep13.md +++ b/test/generators/markdown/Ocamlary.Dep13.md @@ -6,4 +6,4 @@ Module `Ocamlary.Dep13` -###### class [c](Ocamlary.Dep13.c.md) +###### class [c](Ocamlary.Dep13.c.md) diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 64abf0d812..8604199596 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -1048,15 +1048,15 @@ A brown paper package tied up with string -###### class [empty_class](Ocamlary.empty_class.md) +###### class [empty_class](Ocamlary.empty_class.md) -###### class [one_method_class](Ocamlary.one_method_class.md) +###### class [one_method_class](Ocamlary.one_method_class.md) -###### class [two_method_class](Ocamlary.two_method_class.md) +###### class [two_method_class](Ocamlary.two_method_class.md) diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index 5427a97976..79e2bf24f0 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -63,19 +63,19 @@ Doc of `Alias`. -###### class [c1](Toplevel_comments.c1.md) +###### class [c1](Toplevel_comments.c1.md) Doc of `c1`, part 1. -###### class type [ct](Toplevel_comments.class-type-ct.md) +###### class type [ct](Toplevel_comments.class-type-ct.md) Doc of `ct`, part 1. -###### class [c2](Toplevel_comments.c2.md) +###### class [c2](Toplevel_comments.c2.md) Doc of `c2`. From 0b10e6faf41cf355b31b1bc36f00475ca69d3160 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Fri, 11 Feb 2022 13:03:46 +0300 Subject: [PATCH 30/38] remove unnecessary block_separator --- src/markdown/generator.ml | 5 +---- src/markdown/markup.ml | 4 ---- src/markdown/markup.mli | 3 --- test/generators/markdown/Include_sections.md | 10 --------- .../Include_sections.module-type-Something.md | 2 -- test/generators/markdown/Markup.md | 10 --------- test/generators/markdown/Ocamlary.Aliases.md | 2 -- test/generators/markdown/Ocamlary.md | 22 ------------------- ...odule-type-SuperSig.module-type-SubSigA.md | 2 -- ...odule-type-SuperSig.module-type-SubSigB.md | 2 -- test/generators/markdown/Section.md | 2 -- .../Toplevel_comments.Comments_on_open.md | 2 -- test/generators/markdown/mld.md | 6 ----- 13 files changed, 1 insertion(+), 71 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 8ed32ba978..dac4a32520 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -267,10 +267,7 @@ and item (l : Item.t list) args nesting_level = let heading' = let title = inline title args in match label with - | Some _ -> ( - match level with - | 1 -> heading level title - | _ -> blocks (heading level title) block_separator) + | Some _ -> heading level title | None -> paragraph title in blocks heading' (continue rest) diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index c9b8e2561f..9b1d35d0d5 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -18,7 +18,6 @@ type blocks = | CodeBlock of inlines | List of list_type * blocks list | Raw_markup of string - | Block_separator | Prefixed_block of string * blocks (** Prefix every lines of blocks. *) and list_type = Ordered | Unordered @@ -35,8 +34,6 @@ let blocks above below = ConcatB (above, below) let ( +++ ) = blocks -let block_separator = Block_separator - let text s = String s let line_break = Linebreak @@ -118,7 +115,6 @@ let rec pp_blocks fmt b = Format.fprintf fmt "%a@\n%a" pp_blocks above pp_blocks below | Block i -> Format.fprintf fmt "@[%a@]@\n" pp_inlines i | CodeBlock i -> Format.fprintf fmt "```@\n%a@\n```" pp_inlines i - | Block_separator -> Format.fprintf fmt "---@\n" | List (list_type, l) -> let rec pp_list n l = match l with diff --git a/src/markdown/markup.mli b/src/markdown/markup.mli index 4fefb64667..84759b6273 100644 --- a/src/markdown/markup.mli +++ b/src/markdown/markup.mli @@ -46,9 +46,6 @@ val ( +++ ) : blocks -> blocks -> blocks val blocks : blocks -> blocks -> blocks (** Combine blocks. *) -val block_separator : blocks -(** A horizontal line. *) - val raw_markup : string -> blocks val code_span : string -> inlines diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index 82a8c8d973..2e8763f431 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -16,8 +16,6 @@ foo ## Something 2 ---- - # Something 1-bis Some text. @@ -33,16 +31,12 @@ foo ## Something 2 ---- - # Something 1-bis Some text. ## Third include ---- - Shifted some more. # Something 1 @@ -51,8 +45,6 @@ foo ## Something 2 ---- - # Something 1-bis Some text. @@ -78,8 +70,6 @@ foo ## Something 2 ---- - ###### val bar : diff --git a/test/generators/markdown/Include_sections.module-type-Something.md b/test/generators/markdown/Include_sections.module-type-Something.md index 6cbef4248e..fd7b849c03 100644 --- a/test/generators/markdown/Include_sections.module-type-Something.md +++ b/test/generators/markdown/Include_sections.module-type-Something.md @@ -24,8 +24,6 @@ foo ## Something 2 ---- - ###### val bar : diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 0e29849830..cc3228217c 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -13,35 +13,25 @@ Besides the section heading above, there are also ## Subsection headings ---- - and ### Sub-subsection headings ---- - but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. ### Anchors ---- - Sections can have attached [Anchors](#anchors), and it is possible to [link](#anchors) to them. Links to section headers should not be set in source code style. #### Paragraph ---- - Individual paragraphs can have a heading. ##### Subparagraph ---- - Parts of a longer paragraph that can be considered alone can also have headings. diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index c8776b354c..df5c994a82 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -56,8 +56,6 @@ Let's imitate jst's layout. ### include of Foo ---- - Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases.Foo.md). diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 8604199596..748bf8ffc7 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -87,20 +87,12 @@ An unassociated comment ## Level 2 ---- - ### Level 3 ---- - #### Level 4 ---- - ### Basic module stuff ---- - ###### module [Empty](Ocamlary.Empty.md) @@ -131,8 +123,6 @@ A plain module alias of `Empty` ### EmptySig ---- - ###### module type [EmptySig](Ocamlary.module-type-EmptySig.md) @@ -193,8 +183,6 @@ Some text before exception title. ### Basic exception stuff ---- - After exception title. @@ -230,8 +218,6 @@ Unary exception constructor over binary tuple ### Basic type and value stuff with advanced doc comments ---- - ###### type ('a, 'b) a_function = @@ -325,8 +311,6 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. ### Some Operators ---- - ###### val (~-) : @@ -413,8 +397,6 @@ This value has had changes in 1.0.0, 1.1.0, and 1.2.0. ### Advanced Module Stuff ---- - ###### module [CollectionModule](Ocamlary.CollectionModule.md) @@ -485,8 +467,6 @@ This comment is for `IncludeModuleType`. ### Advanced Type Stuff ---- - ###### type record = { @@ -1271,8 +1251,6 @@ features. This documentation demonstrates: ### Weirder usages involving module types ---- - @[`IncludeInclude1.IncludeInclude2_M`](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) @[`Dep4.X`](Ocamlary.Dep4.X.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md index 76590cb4d3..5dd0dd483f 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -8,8 +8,6 @@ Module type `SuperSig.SubSigA` ### A Labeled Section Header Inside of a Signature ---- - ###### type t diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md index 3cebb11dd4..b8a214b178 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md @@ -8,8 +8,6 @@ Module type `SuperSig.SubSigB` ### Another Labeled Section Header Inside of a Signature ---- - ###### type t diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index ff8bfee975..10bcca8174 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -28,8 +28,6 @@ Foo bar. ## and one with a nested section ---- - # _This_ `section` **title** has markup But links are impossible thanks to the parser, so we never have trouble diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md index c2aea27441..6389c8bf65 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -10,7 +10,5 @@ Module `Toplevel_comments.Comments_on_open` ## Section ---- - Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index 88fbb1206b..a99de7ddc8 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -2,8 +2,6 @@ mld Mld Page ---- - This is an `.mld` file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. @@ -23,8 +21,6 @@ Another paragraph in section 2. ## Subsection ---- - This is a subsection. Another paragraph in subsection. @@ -33,8 +29,6 @@ Yet another paragraph in subsection. ## Another Subsection ---- - This is another subsection. Another paragraph in subsection 2. From 93c66f66a362baee4a540a77c05c6e7b596ce4d4 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Fri, 11 Feb 2022 10:55:08 +0100 Subject: [PATCH 31/38] Escape backticks --- src/markdown/markup.ml | 14 +++++++++++++- test/generators/markdown/Ocamlary.md | 12 ++++++------ test/generators/markdown/Recent.md | 8 ++++---- test/generators/markdown/Type.md | 8 ++++---- 4 files changed, 27 insertions(+), 15 deletions(-) diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 9b1d35d0d5..4730ae9cc0 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -34,7 +34,19 @@ let blocks above below = ConcatB (above, below) let ( +++ ) = blocks -let text s = String s +(** Returns two substrings of [s]: The beginning of [s] until [c] occurs, the + rest without the first [c]. Raise [Not_found]. *) +let string_cut_at_char s c = + let len = String.length s in + let i = String.index s c in + (String.sub s 0 i, String.sub s (i + 1) (len - i - 1)) + +let rec text s = + try + (* Escape backticks. *) + let left, right = string_cut_at_char s '`' in + String left ++ String "\\`" ++ text right + with Not_found -> String s let line_break = Linebreak diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 748bf8ffc7..cc6a507180 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -717,13 +717,13 @@ This comment is for `poly_variant_union`. ###### type 'a open_poly_variant = -> [> `TagA ] as 'a +> [> \`TagA ] as 'a ###### type 'a open_poly_variant2 = -> [> `ConstrB of int ] as 'a +> [> \`ConstrB of int ] as 'a @@ -736,25 +736,25 @@ This comment is for `poly_variant_union`. ###### type 'a poly_fun = -> [> `ConstrB of int ] as 'a -> 'a +> [> \`ConstrB of int ] as 'a -> 'a ###### type 'a poly_fun_constraint = -> 'a -> 'a constraint 'a = [> `TagA ] +> 'a -> 'a constraint 'a = [> \`TagA ] ###### type 'a closed_poly_variant = -> [< `One | `Two ] as 'a +> [< \`One | \`Two ] as 'a ###### type 'a clopen_poly_variant = -> [< `One | `Two of int | `Three Two Three ] as 'a +> [< \`One | \`Two of int | \`Three Two Three ] as 'a diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 7c301c6aa8..b4ef9d7d1e 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -112,7 +112,7 @@ bar -######    | X : [< `X of & 'a & int * float ] -> +######    | X : [< \`X of & 'a & int * float ] -> [empty_conj](#type-empty_conj) @@ -121,20 +121,20 @@ bar -######    | X : [< `X of int & [< `B of int & float ] ] -> +######    | X : [< \`X of int & [< \`B of int & float ] ] -> [conj](#type-conj) ###### val empty_conj : -> [< `X of & 'a & int * float ] +> [< \`X of & 'a & int * float ] ###### val conj : -> [< `X of int & [< `B of int & float ] ] +> [< \`X of int & [< \`B of int & float ] ] diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index cc01ba4542..3a7aff671e 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -92,7 +92,7 @@ Some _documentation_. > > [labeled_higher_order](#type-labeled_higher_order) -> -> [ `Bar | `Baz of +> [ \`Bar | \`Baz of > [triple](#type-triple) ] -> > [pair](#type-pair) > -> @@ -340,13 +340,13 @@ _bar_ ###### type 'a exact_variant = -> 'a constraint 'a = [ `A | `B of int ] +> 'a constraint 'a = [ \`A | \`B of int ] ###### type 'a lower_variant = -> 'a constraint 'a = [> `A | `B of int ] +> 'a constraint 'a = [> \`A | \`B of int ] @@ -358,7 +358,7 @@ _bar_ ###### type 'a upper_variant = -> 'a constraint 'a = [< `A | `B of int ] +> 'a constraint 'a = [< \`A | \`B of int ] From b38f9b687792c27286bad6da45aa1ddb36961e18 Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Fri, 11 Feb 2022 11:33:47 +0100 Subject: [PATCH 32/38] Use Astring - Remove custom string functions - Ensure compatibility --- src/markdown/generator.ml | 29 ++++++++++------------------- src/markdown/markup.ml | 36 ++++++++++++++---------------------- 2 files changed, 24 insertions(+), 41 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index dac4a32520..8c2c94b5c1 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -2,6 +2,7 @@ open Odoc_document open Types open Doctree open Markup +open Astring (** Make a new string by copying the given string [n] times. *) let string_repeat n s = @@ -12,21 +13,6 @@ let string_repeat n s = done; Bytes.unsafe_to_string b -(** Like [String.index_from_opt] but check against a predicate function. *) -let rec string_index_f f s i = - if i >= String.length s then None - else if f s.[i] then Some i - else string_index_f f s (i + 1) - -(** Remove spaces at the end of a string. *) -let string_trim_right s = - let right = String.length s - 1 in - let i = ref right in - while !i >= 0 && s.[!i] = ' ' do - decr i - done; - if !i = right then s else String.sub s 0 (!i + 1) - let style (style : style) = match style with | `Bold -> bold @@ -76,7 +62,12 @@ let source_take_until_punctuation code = in let rec inline_take_until_punctuation acc = function | ({ Inline.desc = Text s; _ } as inline) :: tl when is_punctuation s 0 -> - let inline = { inline with desc = Text (string_trim_right s) } in + let inline = + { + inline with + desc = Text (String.drop ~rev:true ~sat:Char.Ascii.is_blank s); + } + in Some (List.rev (inline :: acc), tl) | hd :: tl -> inline_take_until_punctuation (hd :: acc) tl | [] -> None @@ -98,10 +89,10 @@ let is_not_whitespace = function ' ' -> false | _ -> true let rec inline_trim_begin = function | ({ Inline.desc = Text s; _ } as inline) :: tl -> ( - match string_index_f is_not_whitespace s 0 with + match String.find is_not_whitespace s with | None -> inline_trim_begin tl | Some i -> - let s = String.sub s i (String.length s - i) in + let s = String.with_range ~first:i s in { inline with desc = Text s } :: tl) | x -> x @@ -130,7 +121,7 @@ let source_code_to_string s = | Tag (_, t) -> List.rev_append (source_code t) acc) [] s in - String.concat "" (List.rev (source_code s)) + String.concat (List.rev (source_code s)) let rec source_code (s : Source.t) args = fold_inlines (source_code_one args) s diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml index 4730ae9cc0..1be4eb4aa8 100644 --- a/src/markdown/markup.ml +++ b/src/markdown/markup.ml @@ -1,3 +1,5 @@ +open Astring + (* What we need in the markdown generator: Special syntaxes: - Pandoc's heading attributes @@ -34,19 +36,12 @@ let blocks above below = ConcatB (above, below) let ( +++ ) = blocks -(** Returns two substrings of [s]: The beginning of [s] until [c] occurs, the - rest without the first [c]. Raise [Not_found]. *) -let string_cut_at_char s c = - let len = String.length s in - let i = String.index s c in - (String.sub s 0 i, String.sub s (i + 1) (len - i - 1)) - let rec text s = - try - (* Escape backticks. *) - let left, right = string_cut_at_char s '`' in - String left ++ String "\\`" ++ text right - with Not_found -> String s + match String.cut ~sep:"`" s with + | Some (left, right) -> + (* Escape backticks. *) + String left ++ String "\\`" ++ text right + | None -> String s let line_break = Linebreak @@ -64,7 +59,7 @@ let superscript i = Join (String "", Join (i, String "")) let code_span s = let left, right = - if String.contains s '`' then (String "`` ", String " ``") + if String.is_infix ~affix:"`" s then (String "`` ", String " ``") else (String "`", String "`") in Join (left, Join (String s, right)) @@ -84,19 +79,16 @@ let quote_block b = Prefixed_block ("> ", b) let noop_block = Block Noop let heading level i = - let make_hashes n = String.make n '#' in + let make_hashes n = String.v ~len:n (fun _ -> '#') in let hashes = make_hashes level in Block (String hashes ++ String " " ++ i) -(** [split_on_char] is not available on [< 4.04]. *) let rec iter_lines f s i = - try - let i' = String.index_from s i '\n' in - f (String.sub s i (i' - i)); - iter_lines f s (i' + 1) - with Not_found -> - let len = String.length s in - if i < len then f (String.sub s i (len - i)) + match String.find_sub ~start:i ~sub:"\n" s with + | Some i' -> + f (String.with_index_range ~first:i ~last:(i' - 1) s); + iter_lines f s (i' + 1) + | None -> if i < String.length s then f (String.with_range ~first:i s) (** Every lines that [f] formats are prefixed and written in [sink]. Inefficient. *) From 4389a34706300a50a55809faceafd088a69e6eee Mon Sep 17 00:00:00 2001 From: Jules Aguillon Date: Fri, 11 Feb 2022 11:39:22 +0100 Subject: [PATCH 33/38] Properly handle HTML entities The document contains HTML entities that we can match specifically. For future proofing, any other entity can use the HTML syntax. --- src/markdown/generator.ml | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 8c2c94b5c1..be3a10e4dc 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -123,11 +123,13 @@ let source_code_to_string s = in String.concat (List.rev (source_code s)) +(** Special case common entities for readability. *) +let entity = function "#45" -> "-" | "gt" -> ">" | e -> "&" ^ e ^ ";" + let rec source_code (s : Source.t) args = fold_inlines (source_code_one args) s and source_code_one args = function | Source.Elt i -> inline i args - | Tag (Some "arrow", _) -> text "->" | Tag (_, s) -> source_code s args and inline l args = fold_inlines (inline_one args) l @@ -136,7 +138,7 @@ and inline_one args i = match i.Inline.desc with | Text " " -> space | Text s -> text s - | Entity _ -> noop + | Entity e -> text (entity e) | Styled (styl, content) -> style styl (inline content args) | Linebreak -> line_break | Link (href, content) -> link ~href (inline content args) From 6627327788cff9ba8f7fb509f03961f56be72d92 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Fri, 11 Feb 2022 13:09:17 +0300 Subject: [PATCH 34/38] block quote variant constructors --- src/markdown/generator.ml | 26 +- test/generators/markdown/Alias.X.md | 3 +- test/generators/markdown/Bugs.md | 4 +- test/generators/markdown/Bugs_post_406.md | 3 +- test/generators/markdown/Include.md | 12 +- .../markdown/Include2.Y_include_synopsis.md | 3 +- test/generators/markdown/Include2.md | 3 +- test/generators/markdown/Include_sections.md | 6 +- test/generators/markdown/Labels.md | 8 +- test/generators/markdown/Markup.md | 53 +--- test/generators/markdown/Module.md | 4 +- test/generators/markdown/Nested.F.md | 3 +- test/generators/markdown/Ocamlary.Aliases.md | 6 +- .../Ocamlary.CanonicalTest.Base_Tests.md | 6 +- .../Ocamlary.CollectionModule.InnerModuleA.md | 6 +- test/generators/markdown/Ocamlary.ExtMod.md | 2 +- ...peOf.argument-1-Collection.InnerModuleA.md | 6 +- ...ary.FunctorTypeOf.argument-1-Collection.md | 3 +- .../markdown/Ocamlary.IncludeInclude1.md | 6 +- .../markdown/Ocamlary.ModuleWithSignature.md | 3 +- .../Ocamlary.Recollection.InnerModuleA.md | 6 +- ....Recollection.argument-1-C.InnerModuleA.md | 6 +- .../Ocamlary.Recollection.argument-1-C.md | 3 +- test/generators/markdown/Ocamlary.md | 228 +++++++----------- .../Ocamlary.module-type-A.Q.InnerModuleA.md | 6 +- .../Ocamlary.module-type-B.Q.InnerModuleA.md | 6 +- .../Ocamlary.module-type-C.Q.InnerModuleA.md | 6 +- ...ary.module-type-COLLECTION.InnerModuleA.md | 6 +- ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 6 +- .../Ocamlary.module-type-NestedInclude1.md | 3 +- ...le-type-RecollectionModule.InnerModuleA.md | 6 +- ...Ocamlary.module-type-RecollectionModule.md | 3 +- .../Ocamlary.module-type-SigForMod.Inner.md | 3 +- .../markdown/Ocamlary.module-type-SuperSig.md | 12 +- ...odule-type-SuperSig.module-type-SubSigA.md | 3 +- .../Ocamlary.module-type-ToInclude.md | 3 +- .../markdown/Ocamlary.module-type-TypeExt.md | 2 +- .../Ocamlary.module-type-TypeExtPruned.md | 2 +- test/generators/markdown/Recent.md | 34 ++- .../markdown/Recent.module-type-PolyS.md | 6 +- test/generators/markdown/Recent_impl.B.md | 2 +- test/generators/markdown/Recent_impl.Foo.A.md | 2 +- test/generators/markdown/Recent_impl.Foo.B.md | 2 +- test/generators/markdown/Section.md | 4 +- test/generators/markdown/Stop.md | 10 +- .../generators/markdown/Stop_dead_link_doc.md | 12 +- .../Toplevel_comments.Comments_on_open.md | 3 +- .../Toplevel_comments.Ref_in_synopsis.md | 3 +- test/generators/markdown/Toplevel_comments.md | 9 +- test/generators/markdown/Type.md | 85 +++---- test/generators/markdown/mld.md | 3 +- 51 files changed, 240 insertions(+), 411 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index be3a10e4dc..13ca3b6b77 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -31,7 +31,9 @@ type args = { base_path : Url.Path.t; generate_links : bool } let rec source_contains_text (s : Source.t) = let inline_contains_text (i : Inline.t) = let check_inline_desc (i : Inline.desc) = - match i with Text "" | Text " " -> false | Text _ | _ -> true + match i with + | Text ("" | " " | "[ " | " ]" | "{ " | "}") -> false + | Text _ | _ -> true in List.exists (fun { Inline.desc = d; _ } -> check_inline_desc d) i in @@ -132,11 +134,10 @@ and source_code_one args = function | Source.Elt i -> inline i args | Tag (_, s) -> source_code s args -and inline l args = fold_inlines (inline_one args) l +and inline l args = fold_inlines (fun i -> inline_one args i inline_one') l -and inline_one args i = +and inline_one args i inline_one' = match i.Inline.desc with - | Text " " -> space | Text s -> text s | Entity e -> text (entity e) | Styled (styl, content) -> style styl (inline content args) @@ -149,10 +150,16 @@ and inline_one args i = (inline content args) else inline content args | InternalLink (Unresolved content) -> inline content args + | Raw_markup (_, s) -> text s + | _ -> inline_one' args i + +and inline_one' args i = + match i.Inline.desc with + | Text ("" | " " | "[ " | " ]" | "{" | "}") -> space | Source content when source_contains_only_text content -> code_span (source_code_to_string content) | Source content -> source_code content args - | Raw_markup (_, s) -> text s + | _ -> noop let rec block args l = fold_blocks (block_one args) l @@ -235,10 +242,15 @@ and documented args nesting_level content doc anchor = let nesting_level = nesting_level + 1 in match content with | `D code (* for record fields and polymorphic variants *) -> - item_heading nesting_level (inline code args) + let rec inline args = + fold_inlines (fun i -> inline_one args i inline_one') code + and inline_one' args i = + match i.Inline.desc with Source s -> source_code s args | _ -> noop + in + quote_block (paragraph (inline args)) | `N l (* for constructors *) -> let c, rest = take_code l in - item_heading nesting_level (source_code c args) + quote_block (paragraph (source_code c args)) +++ documented_src rest args nesting_level in let item = blocks content (block args doc) in diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md index 898ce2802e..e7dc9b97f6 100644 --- a/test/generators/markdown/Alias.X.md +++ b/test/generators/markdown/Alias.X.md @@ -10,5 +10,4 @@ Module `Alias.X` > int -Module Foo__X documentation. This should appear in the documentation for the -alias to this module 'X' +Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index ee6dd795d6..e7454c4b4b 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -14,6 +14,4 @@ Module `Bugs` > ?bar:'a -> unit -> unit -Triggers an assertion failure when -[https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) -is not fixed. +Triggers an assertion failure when [https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) is not fixed. diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index 9245984a08..6b7b6e3ce4 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -2,8 +2,7 @@ Bugs_post_406 Module `Bugs_post_406` -Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was -added to the language in 4.06 +Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 diff --git a/test/generators/markdown/Include.md b/test/generators/markdown/Include.md index 46c19b8ce6..f501f79229 100644 --- a/test/generators/markdown/Include.md +++ b/test/generators/markdown/Include.md @@ -20,16 +20,13 @@ Module `Include` -###### module type -[Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) +###### module type [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -include -[Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) +include [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -###### module type -[Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) +###### module type [Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) @@ -41,8 +38,7 @@ include -###### module type -[Dorminant_Module](Include.module-type-Dorminant_Module.md) +###### module type [Dorminant_Module](Include.module-type-Dorminant_Module.md) diff --git a/test/generators/markdown/Include2.Y_include_synopsis.md b/test/generators/markdown/Include2.Y_include_synopsis.md index ce0e611349..8b09197382 100644 --- a/test/generators/markdown/Include2.Y_include_synopsis.md +++ b/test/generators/markdown/Include2.Y_include_synopsis.md @@ -4,8 +4,7 @@ Y_include_synopsis Module `Include2.Y_include_synopsis` -The `include Y` below should have the synopsis from `Y`'s top-comment -attached to it. +The `include Y` below should have the synopsis from `Y`'s top-comment attached to it. diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index 1feb8a5d95..a2468d6fd6 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -26,8 +26,7 @@ Top-comment of Y. ###### module [Y_include_synopsis](Include2.Y_include_synopsis.md) -The `include Y` below should have the synopsis from `Y`'s top-comment -attached to it. +The `include Y` below should have the synopsis from `Y`'s top-comment attached to it. diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index 2e8763f431..606f50ec59 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -22,8 +22,7 @@ Some text. # Second include -Let's include [`Something`](Include_sections.module-type-Something.md) a -second time: the heading level should be shift here. +Let's include [`Something`](Include_sections.module-type-Something.md) a second time: the heading level should be shift here. # Something 1 @@ -49,8 +48,7 @@ foo Some text. -And let's include it again, but without inlining it this time: the ToC -shouldn't grow. +And let's include it again, but without inlining it this time: the ToC shouldn't grow. diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index 1ae51b6212..c2078fb6a0 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -62,7 +62,7 @@ Attached to exception -######    | X +> | X Attached to extension @@ -88,7 +88,7 @@ Attached to type subst -######    | A' +> | A' Attached to constructor @@ -98,12 +98,10 @@ Attached to constructor -######    f : [t](#type-t); +> f : [t](#type-t); Attached to field -} - Testing that labels can be referenced - [Attached to unit](#L1) diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index cc3228217c..7d2d3355fe 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -6,8 +6,7 @@ Here, we test the rendering of comment markup. # Sections -Let's get these done first, because sections will be used to break up the -rest of this test. +Let's get these done first, because sections will be used to break up the rest of this test. Besides the section heading above, there are also @@ -17,14 +16,11 @@ and ### Sub-subsection headings -but odoc has banned deeper headings. There are also title headings, but they -are only allowed in mld files. +but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. ### Anchors -Sections can have attached [Anchors](#anchors), and it is possible to -[link](#anchors) to them. Links to section headers should not be set in -source code style. +Sections can have attached [Anchors](#anchors), and it is possible to [link](#anchors) to them. Links to section headers should not be set in source code style. #### Paragraph @@ -32,26 +28,17 @@ Individual paragraphs can have a heading. ##### Subparagraph -Parts of a longer paragraph that can be considered alone can also have -headings. +Parts of a longer paragraph that can be considered alone can also have headings. # Styling -This paragraph has some styled elements: **bold** and _italic_, **_bold -italic_**, _emphasis_, __emphasis_ within emphasis_, **_bold italic_**, -superscript, subscript. The line spacing should be -enough for superscripts and subscripts not to look odd. +This paragraph has some styled elements: **bold** and _italic_, **_bold italic_**, _emphasis_, __emphasis_ within emphasis_, **_bold italic_**, superscript, subscript. The line spacing should be enough for superscripts and subscripts not to look odd. -Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ -emphasis_ is rendered in italics._ _It also work the same in [links in -italics with _emphasis _in_ emphasis_.](#)_ +Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ emphasis_ is rendered in italics._ _It also work the same in [links in italics with _emphasis _in_ emphasis_.](#)_ `code` is a different kind of markup that doesn't allow nested markup. -It's possible for two markup elements to appear **next** _to_ each other and -have a space, and appear **next**_to_ each other with no space. It doesn't -matter **how** _much_ space it was in the source: in this sentence, it was -two space characters. And in this one, there is **a** _newline_. +It's possible for two markup elements to appear **next** _to_ each other and have a space, and appear **next**_to_ each other with no space. It doesn't matter **how** _much_ space it was in the source: in this sentence, it was two space characters. And in this one, there is **a** _newline_. This is also true between _non-_`code` markup _and_ `code`. @@ -59,23 +46,9 @@ Code can appear **inside `other` markup**. Its display shouldn't be affected. # Links and references -This is a [link](#). It sends you to the top of this page. Links can have -markup inside them: [**bold**](#), [_italics_](#), [_emphasis_](#), -[superscript](#), [subscript](#), and [`code`](#). -Links can also be nested _[inside](#)_ markup. Links cannot be nested inside -each other. This link has no replacement text: [#](#). The text is filled in -by odoc. This is a shorthand link: [#](#). The text is also filled in by odoc -in this case. - -This is a reference to [`foo`](#val-foo). References can have replacement -text: [the value foo](#val-foo). Except for the special lookup support, -references are pretty much just like links. The replacement text can have -nested styles: [**bold**](#val-foo), [_italic_](#val-foo), -[_emphasis_](#val-foo), [superscript](#val-foo), -[subscript](#val-foo), and [`code`](#val-foo). It's also possible -to surround a reference in a style: **[`foo`](#val-foo)**. References can't -be nested inside references, and links and references can't be nested inside -each other. +This is a [link](#). It sends you to the top of this page. Links can have markup inside them: [**bold**](#), [_italics_](#), [_emphasis_](#), [superscript](#), [subscript](#), and [`code`](#). Links can also be nested _[inside](#)_ markup. Links cannot be nested inside each other. This link has no replacement text: [#](#). The text is filled in by odoc. This is a shorthand link: [#](#). The text is also filled in by odoc in this case. + +This is a reference to [`foo`](#val-foo). References can have replacement text: [the value foo](#val-foo). Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: [**bold**](#val-foo), [_italic_](#val-foo), [_emphasis_](#val-foo), [superscript](#val-foo), [subscript](#val-foo), and [`code`](#val-foo). It's also possible to surround a reference in a style: **[`foo`](#val-foo)**. References can't be nested inside references, and links and references can't be nested inside each other. # Preformatted text @@ -112,8 +85,7 @@ The main difference is these don't get syntax highlighting. 2. shorthand numbered list. -- Shorthand list items can span multiple lines, however trying to put two - paragraphs into a shorthand list item using a double line break +- Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break just creates a paragraph outside the list. @@ -154,8 +126,7 @@ The parser supports any ASCII-compatible encoding, in particuλar UTF-8. # Raw HTML -Raw HTML can be as inline elements -into sentences. +Raw HTML can be as inline elements into sentences.
diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index e91ef0e152..a13234fd54 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -10,9 +10,7 @@ Foo. > unit -The module needs at least one signature item, otherwise a bug causes the -compiler to drop the module comment (above). See -[https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701). +The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See [https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701). diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md index d9984c3fa4..9fbdebcd09 100644 --- a/test/generators/markdown/Nested.F.md +++ b/test/generators/markdown/Nested.F.md @@ -26,7 +26,6 @@ Some additional comments. ###### type t = -> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) -> * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) +> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) Some type. diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index df5c994a82..0389bd3eee 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -56,8 +56,7 @@ Let's imitate jst's layout. ### include of Foo -Just for giggle, let's see what happens when we include -[`Foo`](Ocamlary.Aliases.Foo.md). +Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases.Foo.md). @@ -93,8 +92,7 @@ Just for giggle, let's see what happens when we include > [A.t](Ocamlary.Aliases.Foo.A.md#type-t) -And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and -[`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) +And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and [`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md index de7a6f74d2..4af17993a5 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md @@ -20,15 +20,13 @@ Module `CanonicalTest.Base_Tests` ###### val foo : -> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float -> [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) ###### val bar : -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a -> [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index df7fd595e0..3fed7cc5d7 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -18,14 +18,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md index aafc1ffb6e..c2d25a0082 100644 --- a/test/generators/markdown/Ocamlary.ExtMod.md +++ b/test/generators/markdown/Ocamlary.ExtMod.md @@ -16,4 +16,4 @@ Module `Ocamlary.ExtMod` -######    | Leisureforce +> | Leisureforce diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md index 64ea64131f..8e0bc94e2f 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -20,14 +20,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md index 6844d5a9fa..23ef0effe4 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -20,8 +20,7 @@ This comment is for `collection`. -###### module -[InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) +###### module [InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) This comment is for `InnerModuleA`. diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md index fcabe29698..a9ce8a56b0 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -6,10 +6,8 @@ Module `Ocamlary.IncludeInclude1` -###### module type -[IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) +###### module type [IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) -###### module -[IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) +###### module [IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md index 025db37fd6..564f1a2254 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignature.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md @@ -4,5 +4,4 @@ ModuleWithSignature Module `Ocamlary.ModuleWithSignature` -A plain module of a signature of -[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) +A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index ed0a568395..54d97c07b3 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -18,14 +18,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md index 4ebb36848f..60dbf22d92 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -20,14 +20,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md index 4872455f74..71b46a375b 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -20,8 +20,7 @@ This comment is for `collection`. -###### module -[InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) +###### module [InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) This comment is for `InnerModuleA`. diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index cc6a507180..abe61c8e73 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -2,8 +2,7 @@ Ocamlary Module `Ocamlary` -This is an _interface_ with **all** of the _module system_ features. This -documentation demonstrates: +This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: - comment formatting @@ -50,8 +49,7 @@ David Sheets is the author. @author David Sheets -You may find more information about this HTML documentation renderer at -[github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary). +You may find more information about this HTML documentation renderer at [github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary). This is some verbatim text: @@ -141,13 +139,11 @@ A plain, empty module signature alias of ###### module [ModuleWithSignature](Ocamlary.ModuleWithSignature.md) -A plain module of a signature of -[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) +A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) -###### module -[ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) +###### module [ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) A plain module with an alias signature @@ -165,13 +161,7 @@ There's a signature in a module in this signature. ###### module type [SuperSig](Ocamlary.module-type-SuperSig.md) -For a good time, see -[`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or -[`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or -[`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md). -Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is -the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module -signature. +For a good time, see [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or [`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md). Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module signature. @@ -207,8 +197,7 @@ Unary exception constructor over binary tuple ###### exception EmptySig -[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and -[`EmptySig`](#exception-EmptySig) is this exception. +[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and [`EmptySig`](#exception-EmptySig) is this exception. @@ -224,8 +213,7 @@ Unary exception constructor over binary tuple > 'a -> 'b -[`a_function`](#type-a_function) is this type and -[`a_function`](#val-a_function) is the value below. +[`a_function`](#type-a_function) is this type and [`a_function`](#val-a_function) is the value below. @@ -244,8 +232,7 @@ This is `a_function` with param and return type. ###### val fun_fun_fun : > -> ( ( int, int ) [a_function](#type-a_function), ( unit, unit ) -> [a_function](#type-a_function) ) [a_function](#type-a_function) +> ( ( int, int ) [a_function](#type-a_function), ( unit, unit ) [a_function](#type-a_function) ) [a_function](#type-a_function) @@ -423,8 +410,7 @@ module type of -###### module type -[RecollectionModule](Ocamlary.module-type-RecollectionModule.md) +###### module type [RecollectionModule](Ocamlary.module-type-RecollectionModule.md) @@ -448,8 +434,7 @@ This comment is for `FunctorTypeOf`. -###### module type -[IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) +###### module type [IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) This comment is for `IncludeModuleType`. @@ -473,18 +458,16 @@ This comment is for `IncludeModuleType`. -######    `;int : field1` +> field1 : int; This comment is for `field1`. -######    `;int : field2` +> field2 : int; This comment is for `field2`. -} - This comment is for `record`. This comment is also for `record`. @@ -495,33 +478,29 @@ This comment is also for `record`. -######    `;int : a mutable` +> mutable a : int; `a` is first and mutable -######    `;unit : b` +> b : unit; `b` is second and immutable -######    `;int : c mutable` +> mutable c : int; `c` is third and mutable -} - ###### type universe_record = { -######    nihilate : 'a. 'a -> unit; - -} +> nihilate : 'a. 'a -> unit; @@ -529,25 +508,25 @@ This comment is also for `record`. -######    | TagA +> | TagA This comment is for `TagA`. -######    | ConstrB of int +> | ConstrB of int This comment is for `ConstrB`. -######    | ConstrC of int * int +> | ConstrC of int * int This comment is for binary `ConstrC`. -######    | ConstrD of int * int +> | ConstrD of int * int This comment is for unary `ConstrD` of binary tuple. @@ -561,13 +540,11 @@ This comment is also for `variant`. -######    `| ``` `TagA `` +> | `TagA -######    `| ``` int of `ConstrB `` - - ] +> | `ConstrB of int This comment is for `poly_variant`. @@ -579,19 +556,19 @@ Wow! It was a polymorphic variant! -######    | Tag : ( unit, unit ) [full_gadt](#type-full_gadt) +> | Tag : ( unit, unit ) [full_gadt](#type-full_gadt) -######    | First : 'a -> ( 'a, unit ) [full_gadt](#type-full_gadt) +> | First : 'a -> ( 'a, unit ) [full_gadt](#type-full_gadt) -######    | Second : 'a -> ( unit, 'a ) [full_gadt](#type-full_gadt) +> | Second : 'a -> ( unit, 'a ) [full_gadt](#type-full_gadt) -######    | Exist : 'a * 'b -> ( 'b, unit ) [full_gadt](#type-full_gadt) +> | Exist : 'a * 'b -> ( 'b, unit ) [full_gadt](#type-full_gadt) This comment is for `full_gadt`. @@ -603,16 +580,15 @@ Wow! It was a GADT! -######    | AscribeTag : 'a [partial_gadt](#type-partial_gadt) +> | AscribeTag : 'a [partial_gadt](#type-partial_gadt) -######    | OfTag of 'a [partial_gadt](#type-partial_gadt) +> | OfTag of 'a [partial_gadt](#type-partial_gadt) -######    | ExistGadtTag : ( 'a -> 'b ) -> 'a -[partial_gadt](#type-partial_gadt) +> | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt](#type-partial_gadt) This comment is for `partial_gadt`. @@ -630,8 +606,7 @@ This comment is for `alias`. ###### type tuple = -> ([alias](#type-alias) * [alias](#type-alias)) * [alias](#type-alias) -> * ([alias](#type-alias) * [alias](#type-alias)) +> ([alias](#type-alias) * [alias](#type-alias)) * [alias](#type-alias) * ([alias](#type-alias) * [alias](#type-alias)) This comment is for `tuple`. @@ -641,19 +616,19 @@ This comment is for `tuple`. -######    | TagA +> | TagA -######    | ConstrB of int +> | ConstrB of int -######    | ConstrC of int * int +> | ConstrC of int * int -######    | ConstrD of int * int +> | ConstrD of int * int This comment is for `variant_alias`. @@ -663,13 +638,11 @@ This comment is for `variant_alias`. -######    `;int : field1` +> field1 : int; -######    `;int : field2` - -} +> field2 : int; This comment is for `record_alias`. @@ -679,13 +652,11 @@ This comment is for `record_alias`. -######    `| `[poly_variant](#type-poly_variant) +> | [poly_variant](#type-poly_variant) -######    `| ``` `TagC `` - - ] +> | `TagC This comment is for `poly_variant_union`. @@ -695,9 +666,7 @@ This comment is for `poly_variant_union`. -######    `| ``` 'a of `TagA `` - - ] +> | `TagA of 'a @@ -705,13 +674,11 @@ This comment is for `poly_variant_union`. -######    `| ``` 'a of `TagA `` +> | `TagA of 'a -######    `| ``` 'b of `ConstrB `` - - ] +> | `ConstrB of 'b @@ -729,8 +696,7 @@ This comment is for `poly_variant_union`. ###### type 'a open_poly_variant_alias = -> 'a [open_poly_variant](#type-open_poly_variant) -> [open_poly_variant2](#type-open_poly_variant2) +> 'a [open_poly_variant](#type-open_poly_variant) [open_poly_variant2](#type-open_poly_variant2) @@ -762,45 +728,39 @@ This comment is for `poly_variant_union`. -######    `| ``` `A `` +> | `A -######    `| ``` [ `B1 | `B2 ] of `B `` +> | `B of [ `B1 | `B2 ] -######    `| ``` `C `` +> | `C -######    `| ``` [ [ `D1a ] of`D1 ] of `D `` - - ] +> | `D of [ `D1 of [ `D1a ] ] -###### type ('a, 'b) full_gadt_alias = ( 'a, 'b ) -[full_gadt](#type-full_gadt) = +###### type ('a, 'b) full_gadt_alias = ( 'a, 'b ) [full_gadt](#type-full_gadt) = -######    | Tag : ( unit, unit ) [full_gadt_alias](#type-full_gadt_alias) +> | Tag : ( unit, unit ) [full_gadt_alias](#type-full_gadt_alias) -######    | First : 'a -> ( 'a, unit ) -[full_gadt_alias](#type-full_gadt_alias) +> | First : 'a -> ( 'a, unit ) [full_gadt_alias](#type-full_gadt_alias) -######    | Second : 'a -> ( unit, 'a ) -[full_gadt_alias](#type-full_gadt_alias) +> | Second : 'a -> ( unit, 'a ) [full_gadt_alias](#type-full_gadt_alias) -######    | Exist : 'a * 'b -> ( 'b, unit ) -[full_gadt_alias](#type-full_gadt_alias) +> | Exist : 'a * 'b -> ( 'b, unit ) [full_gadt_alias](#type-full_gadt_alias) This comment is for `full_gadt_alias`. @@ -810,16 +770,15 @@ This comment is for `full_gadt_alias`. -######    | AscribeTag : 'a [partial_gadt_alias](#type-partial_gadt_alias) +> | AscribeTag : 'a [partial_gadt_alias](#type-partial_gadt_alias) -######    | OfTag of 'a [partial_gadt_alias](#type-partial_gadt_alias) +> | OfTag of 'a [partial_gadt_alias](#type-partial_gadt_alias) -######    | ExistGadtTag : ( 'a -> 'b ) -> 'a -[partial_gadt_alias](#type-partial_gadt_alias) +> | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt_alias](#type-partial_gadt_alias) This comment is for `partial_gadt_alias`. @@ -837,17 +796,15 @@ This comment is for [`Exn_arrow`](#exception-Exn_arrow). -######    | A +> | A -######    | B_ish of [mutual_constr_b](#type-mutual_constr_b) +> | B_ish of [mutual_constr_b](#type-mutual_constr_b) -This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and -[`mutual_constr_b`](#type-mutual_constr_b). +This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and [`mutual_constr_b`](#type-mutual_constr_b). -This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then -[`mutual_constr_b`](#type-mutual_constr_b). +This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then [`mutual_constr_b`](#type-mutual_constr_b). @@ -855,16 +812,15 @@ This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then -######    | B +> | B -######    | A_ish of [mutual_constr_a](#type-mutual_constr_a) +> | A_ish of [mutual_constr_a](#type-mutual_constr_a) This comment must be here for the next to associate correctly. -This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then -[`mutual_constr_a`](#type-mutual_constr_a). +This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then [`mutual_constr_a`](#type-mutual_constr_a). @@ -916,7 +872,7 @@ A mystery wrapped in an ellipsis -######    | ExtA +> | ExtA @@ -924,7 +880,7 @@ A mystery wrapped in an ellipsis -######    | ExtB +> | ExtB @@ -932,11 +888,11 @@ A mystery wrapped in an ellipsis -######    | ExtC of unit +> | ExtC of unit -######    | ExtD of [ext](#type-ext) +> | ExtD of [ext](#type-ext) @@ -944,7 +900,7 @@ A mystery wrapped in an ellipsis -######    | ExtE +> | ExtE @@ -952,7 +908,7 @@ A mystery wrapped in an ellipsis -######    | ExtF +> | ExtF @@ -968,11 +924,11 @@ A mystery wrapped in an ellipsis -######    | Foo of 'b +> | Foo of 'b -######    | Bar of 'b * 'b +> | Bar of 'b * 'b 'b poly_ext @@ -982,7 +938,7 @@ A mystery wrapped in an ellipsis -######    | Quux of 'c +> | Quux of 'c 'c poly_ext @@ -996,7 +952,7 @@ A mystery wrapped in an ellipsis -######    | ZzzTop0 +> | ZzzTop0 It's got the rock @@ -1006,7 +962,7 @@ It's got the rock -######    | ZzzTop of unit +> | ZzzTop of unit and it packs a unit. @@ -1236,18 +1192,16 @@ A brown paper package tied up with string # Trying the {!modules: ...} command. -With ocamldoc, toplevel units will be linked and documented, while submodules -will behave as simple references. +With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references. -With odoc, everything should be resolved (and linked) but only toplevel units -will be documented. +With odoc, everything should be resolved (and linked) but only toplevel units will be documented. @[`Dep1.X`](Ocamlary.Dep1.X.md) @[`Ocamlary.IncludeInclude1`](Ocamlary.IncludeInclude1.md) -@[`Ocamlary`]() This is an _interface_ with **all** of the _module system_ -features. This documentation demonstrates: +@[`Ocamlary`]() +This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: ### Weirder usages involving module types @@ -1261,12 +1215,7 @@ features. This documentation demonstrates: ###### module [CanonicalTest](Ocamlary.CanonicalTest.md) -Some ref to -[`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) -and -[`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id). -But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) -and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) +Some ref to [`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) and [`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id). But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) # Aliases again @@ -1280,8 +1229,7 @@ Let's imitate jst's layout. I can refer to -- `{!section:indexmodules}` : [Trying the {!modules: ...} - command.](#indexmodules) +- `{!section:indexmodules}` : [Trying the {!modules: ...} command.](#indexmodules) - `{!aliases}` : [Aliases again](#aliases) @@ -1289,8 +1237,7 @@ I can refer to But also to things in submodules: -- `{!section:SuperSig.SubSigA.subSig}` : - [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{!section:SuperSig.SubSigA.subSig}` : [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) - `{!Aliases.incl}` : [`incl`](Ocamlary.Aliases.md#incl) @@ -1304,8 +1251,7 @@ And just to make sure we do not mess up: - `{{!aliases}B}` : [B](#aliases) -- `{{!section:SuperSig.SubSigA.subSig}C}` : - [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{{!section:SuperSig.SubSigA.subSig}C}` : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) - `{{!Aliases.incl}D}` : [D](Ocamlary.Aliases.md#incl) @@ -1333,20 +1279,16 @@ Here goes: ###### module [Only_a_module](Ocamlary.Only_a_module.md) -- `{!Only_a_module.t}` : - [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!module-Only_a_module.t}` : - [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!module-Only_a_module.type-t}` : - [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.type-t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!type:Only_a_module.t}` : - [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!type:Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) @@ -1365,7 +1307,7 @@ Here goes: -######    | C +> | C diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md index 888457b937..066b8a008a 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -20,14 +20,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md index 8ba3ae9960..20ed2ed783 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -20,14 +20,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md index 7fb5375ddc..d54c480658 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -20,14 +20,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md index 4cb1c304e0..fed0d24364 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -18,14 +18,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md index 213099c295..011207d5a0 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -20,14 +20,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md index 97726c9f67..f06831974c 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md @@ -6,5 +6,4 @@ Module type `Ocamlary.NestedInclude1` -###### module type -[NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) +###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md index 8b2ecda941..23d4364985 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -18,14 +18,12 @@ This comment is for `t`. -###### module -[InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) +###### module [InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type -[InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type [InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md index c5ae6dad29..3ce0bf479e 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -18,8 +18,7 @@ Module type `Ocamlary.RecollectionModule` -###### module -[InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) +###### module [InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) This comment is for `InnerModuleA`. diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md index 2aee21fad4..2fadb0ac77 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md @@ -8,5 +8,4 @@ Module `SigForMod.Inner` -###### module type -[Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) +###### module type [Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.md index cc52b8ba66..76a9c9ee27 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md @@ -6,18 +6,15 @@ Module type `Ocamlary.SuperSig` -###### module type -[SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) +###### module type [SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) -###### module type -[SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) +###### module type [SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) -###### module type -[EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) +###### module type [EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) @@ -25,5 +22,4 @@ Module type `Ocamlary.SuperSig` -###### module type -[SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) +###### module type [SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md index 5dd0dd483f..adcc45394c 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -14,5 +14,4 @@ Module type `SuperSig.SubSigA` -###### module -[SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) +###### module [SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.md index f4e70e5a10..9583e397a3 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md @@ -10,5 +10,4 @@ Module type `Ocamlary.ToInclude` -###### module type -[IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) +###### module type [IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExt.md b/test/generators/markdown/Ocamlary.module-type-TypeExt.md index a405463f4e..f606b84c58 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExt.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExt.md @@ -16,7 +16,7 @@ Module type `Ocamlary.TypeExt` -######    | C +> | C diff --git a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md index b17195a0fc..f681175728 100644 --- a/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md +++ b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md @@ -10,7 +10,7 @@ Module type `Ocamlary.TypeExtPruned` -######    | C +> | C diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index b4ef9d7d1e..1854ed96a1 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -16,33 +16,31 @@ Module `Recent` -######    | A +> | A -######    | B of int +> | B of int -######    | C +> | C foo -######    | D +> | D _bar_ -######    | E of { +> | E of { -######      `;int : a` - -} +> a : int; @@ -50,23 +48,23 @@ _bar_ -######    | A : int [gadt](#type-gadt) +> | A : int [gadt](#type-gadt) -######    | B : int -> string [gadt](#type-gadt) +> | B : int -> string [gadt](#type-gadt) foo -######    | C : { +> | C : { -######      `;int : a` +> a : int; -} -> unit [gadt](#type-gadt) + -> unit [gadt](#type-gadt) @@ -74,26 +72,24 @@ foo -######    `| ``` `A `` +> | `A -######    `| ``` int of `B `` +> | `B of int -######    `| ``` `C `` +> | `C foo -######    `| ``` `D `` +> | `D bar - ] - ###### type empty_variant = diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index a43c0873b9..d3e91bbd3b 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -10,10 +10,8 @@ Module type `Recent.PolyS` -######    `| ``` `A `` +> | `A -######    `| ``` `B `` - - ] +> | `B diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md index c0cd07c3fd..d974f03450 100644 --- a/test/generators/markdown/Recent_impl.B.md +++ b/test/generators/markdown/Recent_impl.B.md @@ -10,4 +10,4 @@ Module `Recent_impl.B` -######    | B +> | B diff --git a/test/generators/markdown/Recent_impl.Foo.A.md b/test/generators/markdown/Recent_impl.Foo.A.md index fd2b009318..b0ffff3fa9 100644 --- a/test/generators/markdown/Recent_impl.Foo.A.md +++ b/test/generators/markdown/Recent_impl.Foo.A.md @@ -12,4 +12,4 @@ Module `Foo.A` -######    | A +> | A diff --git a/test/generators/markdown/Recent_impl.Foo.B.md b/test/generators/markdown/Recent_impl.Foo.B.md index 609c159967..eff358642e 100644 --- a/test/generators/markdown/Recent_impl.Foo.B.md +++ b/test/generators/markdown/Recent_impl.Foo.B.md @@ -12,4 +12,4 @@ Module `Foo.B` -######    | B +> | B diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index 10bcca8174..b825da564b 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -30,6 +30,4 @@ Foo bar. # _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. +But links are impossible thanks to the parser, so we never have trouble rendering a section title in a table of contents – no link will be nested inside another link. diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md index 10df64d1f7..f075c038c7 100644 --- a/test/generators/markdown/Stop.md +++ b/test/generators/markdown/Stop.md @@ -12,17 +12,11 @@ This test cases exercises stop comments. This is normal commented text. -The next value is `bar`, and it should be missing from the documentation. -There is also an entire module, `M`, which should also be hidden. It contains -a nested stop comment, but that stop comment should not turn documentation -back on in this outer module, because stop comments respect scope. +The next value is `bar`, and it should be missing from the documentation. There is also an entire module, `M`, which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. Documentation is on again. -Now, we have a nested module, and it has a stop comment between its two -items. We want to see that the first item is displayed, but the second is -missing, and the stop comment disables documenation only in that module, and -not in this outer module. +Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module. diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index ce38008812..e3580a5319 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -12,7 +12,7 @@ Module `Stop_dead_link_doc` -######    | Bar of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) +> | Bar of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) @@ -20,13 +20,11 @@ Module `Stop_dead_link_doc` -######    | Bar of { +> | Bar of { -######      field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t); - -} +> field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t); @@ -34,7 +32,7 @@ Module `Stop_dead_link_doc` -######    | Bar_ of int * [Foo.t](Stop_dead_link_doc.Foo.md#type-t) * int +> | Bar_ of int * [Foo.t](Stop_dead_link_doc.Foo.md#type-t) * int @@ -42,7 +40,7 @@ Module `Stop_dead_link_doc` -######    | Bar__ of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) option +> | Bar__ of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) option diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md index 6389c8bf65..08bf35d202 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -10,5 +10,4 @@ Module `Toplevel_comments.Comments_on_open` ## Section -Comments attached to open are treated as floating comments. Referencing -[Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works +Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md index 40045252ec..5b43ef08b5 100644 --- a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -6,8 +6,7 @@ Module `Toplevel_comments.Ref_in_synopsis` [`t`](#type-t). -This reference should resolve in the context of this module, even when used -as a synopsis. +This reference should resolve in the context of this module, even when used as a synopsis. diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index 79e2bf24f0..fb85045525 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -2,8 +2,7 @@ Toplevel_comments Module `Toplevel_comments` -A doc comment at the beginning of a module is considered to be that module's -doc. +A doc comment at the beginning of a module is considered to be that module's doc. @@ -25,15 +24,13 @@ Doc of `Include_inline`, part 1. -###### module type -[Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) +###### module type [Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) Doc of `T`, part 2. -###### module type -[Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) +###### module type [Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) Doc of `Include_inline_T'`, part 1. diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 3a7aff671e..f4d781ba8b 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -97,14 +97,11 @@ Some _documentation_. > [pair](#type-pair) > -> > [labeled](#type-labeled) -> -> [higher_order](#type-higher_order) -> -> +> [higher_order](#type-higher_order) -> > ( string -> int ) -> -> (int * float * char * string * char * unit) -> option -> +> (int * float * char * string * char * unit) option -> > [nested_pair](#type-nested_pair) -> -> [arrow](#type-arrow) -> -> +> [arrow](#type-arrow) -> > string -> > [nested_pair](#type-nested_pair) array @@ -114,9 +111,7 @@ Some _documentation_. -######    `;int : a` - -} +> a : int; @@ -124,27 +119,27 @@ Some _documentation_. -######    | A +> | A -######    | B of int +> | B of int -######    | C +> | C foo -######    | D +> | D _bar_ -######    | E of [variant_e](#type-variant_e) +> | E of [variant_e](#type-variant_e) @@ -152,9 +147,7 @@ _bar_ -######    `;int : a` - -} +> a : int; @@ -162,15 +155,15 @@ _bar_ -######    | A : int [gadt](#type-gadt) +> | A : int [gadt](#type-gadt) -######    | B : int -> string [gadt](#type-gadt) +> | B : int -> string [gadt](#type-gadt) -######    | C : [variant_c](#type-variant_c) -> unit [gadt](#type-gadt) +> | C : [variant_c](#type-variant_c) -> unit [gadt](#type-gadt) @@ -178,7 +171,7 @@ _bar_ -######    | A : [degenerate_gadt](#type-degenerate_gadt) +> | A : [degenerate_gadt](#type-degenerate_gadt) @@ -186,7 +179,7 @@ _bar_ -######    | A +> | A @@ -194,29 +187,27 @@ _bar_ -######    `;int : a` +> a : int; -######    `;int : b mutable` +> mutable b : int; -######    `;int : c` +> c : int; foo -######    `;int : d` +> d : int; _bar_ -######    `;'a'a. : e` - -} +> e : 'a. 'a; @@ -224,21 +215,19 @@ _bar_ -######    `| ``` `A `` +> | `A -######    `| ``` int of `B `` +> | `B of int -######    `| ``` unit* int of `C `` +> | `C of int * unit -######    `| ``` `D `` - - ] +> | `D @@ -246,13 +235,11 @@ _bar_ -######    `| `[polymorphic_variant](#type-polymorphic_variant) +> | [polymorphic_variant](#type-polymorphic_variant) -######    `| ``` `E `` - - ] +> | `E @@ -260,9 +247,7 @@ _bar_ -######    `| ``` [ `B | `C ] of `A `` - - ] +> | `A of [ `B | `C ] @@ -274,9 +259,7 @@ _bar_ -######    `| `[polymorphic_variant](#type-polymorphic_variant) - - ] +> | [polymorphic_variant](#type-polymorphic_variant) @@ -298,9 +281,7 @@ _bar_ ###### type module_substitution = -> (module [X](Type.module-type-X.md) with type -> [t](Type.module-type-X.md#type-t) = int and type -> [u](Type.module-type-X.md#type-u) = unit) +> (module [X](Type.module-type-X.md) with type [t](Type.module-type-X.md#type-t) = int and type [u](Type.module-type-X.md#type-u) = unit) @@ -408,13 +389,13 @@ _bar_ -######    | Extension +> | Extension Documentation for [`Extension`](#extension-Extension). -######    | Another_extension +> | Another_extension Documentation for [`Another_extension`](#extension-Another_extension). @@ -424,7 +405,7 @@ Documentation for [`Another_extension`](#extension-Another_extension). -######    | A of [recursive](#type-recursive) +> | A of [recursive](#type-recursive) @@ -432,7 +413,7 @@ Documentation for [`Another_extension`](#extension-Another_extension). -######    | B of [mutually](#type-mutually) +> | B of [mutually](#type-mutually) diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index a99de7ddc8..3e0cb7a46c 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -2,8 +2,7 @@ mld Mld Page -This is an `.mld` file. It doesn't have an auto-generated title, like modules -and other pages generated fully by odoc do. +This is an `.mld` file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. It will have a TOC generated from section headings. From 67077ec8d49adcd61ec9a511639581343fc26778 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Fri, 11 Feb 2022 13:16:49 +0300 Subject: [PATCH 35/38] add brackets back to record types and variants --- src/markdown/generator.ml | 28 ++--- test/generators/markdown/Alias.X.md | 3 +- test/generators/markdown/Bugs.md | 4 +- test/generators/markdown/Bugs_post_406.md | 3 +- test/generators/markdown/Include.md | 12 +- .../markdown/Include2.Y_include_synopsis.md | 3 +- test/generators/markdown/Include2.md | 3 +- test/generators/markdown/Include_sections.md | 6 +- test/generators/markdown/Labels.md | 2 + test/generators/markdown/Markup.md | 53 +++++++-- test/generators/markdown/Module.md | 4 +- test/generators/markdown/Nested.F.md | 3 +- test/generators/markdown/Ocamlary.Aliases.md | 6 +- .../Ocamlary.CanonicalTest.Base_Tests.md | 6 +- .../Ocamlary.CollectionModule.InnerModuleA.md | 6 +- ...peOf.argument-1-Collection.InnerModuleA.md | 6 +- ...ary.FunctorTypeOf.argument-1-Collection.md | 3 +- .../markdown/Ocamlary.IncludeInclude1.md | 6 +- .../markdown/Ocamlary.ModuleWithSignature.md | 3 +- .../Ocamlary.Recollection.InnerModuleA.md | 6 +- ....Recollection.argument-1-C.InnerModuleA.md | 6 +- .../Ocamlary.Recollection.argument-1-C.md | 3 +- test/generators/markdown/Ocamlary.md | 112 +++++++++++++----- .../Ocamlary.module-type-A.Q.InnerModuleA.md | 6 +- .../Ocamlary.module-type-B.Q.InnerModuleA.md | 6 +- .../Ocamlary.module-type-C.Q.InnerModuleA.md | 6 +- ...ary.module-type-COLLECTION.InnerModuleA.md | 6 +- ...Ocamlary.module-type-MMM.C.InnerModuleA.md | 6 +- .../Ocamlary.module-type-NestedInclude1.md | 3 +- ...le-type-RecollectionModule.InnerModuleA.md | 6 +- ...Ocamlary.module-type-RecollectionModule.md | 3 +- .../Ocamlary.module-type-SigForMod.Inner.md | 3 +- .../markdown/Ocamlary.module-type-SuperSig.md | 12 +- ...odule-type-SuperSig.module-type-SubSigA.md | 3 +- .../Ocamlary.module-type-ToInclude.md | 3 +- test/generators/markdown/Recent.md | 6 +- .../markdown/Recent.module-type-PolyS.md | 2 + test/generators/markdown/Section.md | 4 +- test/generators/markdown/Stop.md | 10 +- .../generators/markdown/Stop_dead_link_doc.md | 2 + .../Toplevel_comments.Comments_on_open.md | 3 +- .../Toplevel_comments.Ref_in_synopsis.md | 3 +- test/generators/markdown/Toplevel_comments.md | 9 +- test/generators/markdown/Type.md | 27 ++++- test/generators/markdown/mld.md | 3 +- 45 files changed, 297 insertions(+), 122 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index 13ca3b6b77..d8c1410bec 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -31,9 +31,7 @@ type args = { base_path : Url.Path.t; generate_links : bool } let rec source_contains_text (s : Source.t) = let inline_contains_text (i : Inline.t) = let check_inline_desc (i : Inline.desc) = - match i with - | Text ("" | " " | "[ " | " ]" | "{ " | "}") -> false - | Text _ | _ -> true + match i with Text ("" | " ") -> false | Text _ | _ -> true in List.exists (fun { Inline.desc = d; _ } -> check_inline_desc d) i in @@ -134,10 +132,11 @@ and source_code_one args = function | Source.Elt i -> inline i args | Tag (_, s) -> source_code s args -and inline l args = fold_inlines (fun i -> inline_one args i inline_one') l +and inline l args = fold_inlines (inline_one args) l -and inline_one args i inline_one' = +and inline_one args i = match i.Inline.desc with + | Text ("" | " ") -> space | Text s -> text s | Entity e -> text (entity e) | Styled (styl, content) -> style styl (inline content args) @@ -150,16 +149,10 @@ and inline_one args i inline_one' = (inline content args) else inline content args | InternalLink (Unresolved content) -> inline content args - | Raw_markup (_, s) -> text s - | _ -> inline_one' args i - -and inline_one' args i = - match i.Inline.desc with - | Text ("" | " " | "[ " | " ]" | "{" | "}") -> space | Source content when source_contains_only_text content -> code_span (source_code_to_string content) | Source content -> source_code content args - | _ -> noop + | Raw_markup (_, s) -> text s let rec block args l = fold_blocks (block_one args) l @@ -242,12 +235,15 @@ and documented args nesting_level content doc anchor = let nesting_level = nesting_level + 1 in match content with | `D code (* for record fields and polymorphic variants *) -> - let rec inline args = - fold_inlines (fun i -> inline_one args i inline_one') code + let rec inline' code args = + fold_inlines (fun i -> inline_one' args i) code and inline_one' args i = - match i.Inline.desc with Source s -> source_code s args | _ -> noop + match i.Inline.desc with + | Source s -> source_code s args + | Text s -> text s + | _ -> inline code args in - quote_block (paragraph (inline args)) + quote_block (paragraph (inline' code args)) | `N l (* for constructors *) -> let c, rest = take_code l in quote_block (paragraph (source_code c args)) diff --git a/test/generators/markdown/Alias.X.md b/test/generators/markdown/Alias.X.md index e7dc9b97f6..898ce2802e 100644 --- a/test/generators/markdown/Alias.X.md +++ b/test/generators/markdown/Alias.X.md @@ -10,4 +10,5 @@ Module `Alias.X` > int -Module Foo__X documentation. This should appear in the documentation for the alias to this module 'X' +Module Foo__X documentation. This should appear in the documentation for the +alias to this module 'X' diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md index e7454c4b4b..ee6dd795d6 100644 --- a/test/generators/markdown/Bugs.md +++ b/test/generators/markdown/Bugs.md @@ -14,4 +14,6 @@ Module `Bugs` > ?bar:'a -> unit -> unit -Triggers an assertion failure when [https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) is not fixed. +Triggers an assertion failure when +[https://github.com/ocaml/odoc/issues/101](https://github.com/ocaml/odoc/issues/101) +is not fixed. diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md index 6b7b6e3ce4..9245984a08 100644 --- a/test/generators/markdown/Bugs_post_406.md +++ b/test/generators/markdown/Bugs_post_406.md @@ -2,7 +2,8 @@ Bugs_post_406 Module `Bugs_post_406` -Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was added to the language in 4.06 +Let-open in class types, https://github.com/ocaml/odoc/issues/543 This was +added to the language in 4.06 diff --git a/test/generators/markdown/Include.md b/test/generators/markdown/Include.md index f501f79229..46c19b8ce6 100644 --- a/test/generators/markdown/Include.md +++ b/test/generators/markdown/Include.md @@ -20,13 +20,16 @@ Module `Include` -###### module type [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) +###### module type +[Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -include [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) +include +[Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -###### module type [Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) +###### module type +[Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md) @@ -38,7 +41,8 @@ include [Not_inlined_and_closed](Include.module-type-Not_inlined_and_closed.md) -###### module type [Dorminant_Module](Include.module-type-Dorminant_Module.md) +###### module type +[Dorminant_Module](Include.module-type-Dorminant_Module.md) diff --git a/test/generators/markdown/Include2.Y_include_synopsis.md b/test/generators/markdown/Include2.Y_include_synopsis.md index 8b09197382..ce0e611349 100644 --- a/test/generators/markdown/Include2.Y_include_synopsis.md +++ b/test/generators/markdown/Include2.Y_include_synopsis.md @@ -4,7 +4,8 @@ Y_include_synopsis Module `Include2.Y_include_synopsis` -The `include Y` below should have the synopsis from `Y`'s top-comment attached to it. +The `include Y` below should have the synopsis from `Y`'s top-comment +attached to it. diff --git a/test/generators/markdown/Include2.md b/test/generators/markdown/Include2.md index a2468d6fd6..1feb8a5d95 100644 --- a/test/generators/markdown/Include2.md +++ b/test/generators/markdown/Include2.md @@ -26,7 +26,8 @@ Top-comment of Y. ###### module [Y_include_synopsis](Include2.Y_include_synopsis.md) -The `include Y` below should have the synopsis from `Y`'s top-comment attached to it. +The `include Y` below should have the synopsis from `Y`'s top-comment +attached to it. diff --git a/test/generators/markdown/Include_sections.md b/test/generators/markdown/Include_sections.md index 606f50ec59..2e8763f431 100644 --- a/test/generators/markdown/Include_sections.md +++ b/test/generators/markdown/Include_sections.md @@ -22,7 +22,8 @@ Some text. # Second include -Let's include [`Something`](Include_sections.module-type-Something.md) a second time: the heading level should be shift here. +Let's include [`Something`](Include_sections.module-type-Something.md) a +second time: the heading level should be shift here. # Something 1 @@ -48,7 +49,8 @@ foo Some text. -And let's include it again, but without inlining it this time: the ToC shouldn't grow. +And let's include it again, but without inlining it this time: the ToC +shouldn't grow. diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index c2078fb6a0..43ebb91ab0 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -102,6 +102,8 @@ Attached to constructor Attached to field +} + Testing that labels can be referenced - [Attached to unit](#L1) diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md index 7d2d3355fe..cc3228217c 100644 --- a/test/generators/markdown/Markup.md +++ b/test/generators/markdown/Markup.md @@ -6,7 +6,8 @@ Here, we test the rendering of comment markup. # Sections -Let's get these done first, because sections will be used to break up the rest of this test. +Let's get these done first, because sections will be used to break up the +rest of this test. Besides the section heading above, there are also @@ -16,11 +17,14 @@ and ### Sub-subsection headings -but odoc has banned deeper headings. There are also title headings, but they are only allowed in mld files. +but odoc has banned deeper headings. There are also title headings, but they +are only allowed in mld files. ### Anchors -Sections can have attached [Anchors](#anchors), and it is possible to [link](#anchors) to them. Links to section headers should not be set in source code style. +Sections can have attached [Anchors](#anchors), and it is possible to +[link](#anchors) to them. Links to section headers should not be set in +source code style. #### Paragraph @@ -28,17 +32,26 @@ Individual paragraphs can have a heading. ##### Subparagraph -Parts of a longer paragraph that can be considered alone can also have headings. +Parts of a longer paragraph that can be considered alone can also have +headings. # Styling -This paragraph has some styled elements: **bold** and _italic_, **_bold italic_**, _emphasis_, __emphasis_ within emphasis_, **_bold italic_**, superscript, subscript. The line spacing should be enough for superscripts and subscripts not to look odd. +This paragraph has some styled elements: **bold** and _italic_, **_bold +italic_**, _emphasis_, __emphasis_ within emphasis_, **_bold italic_**, +superscript, subscript. The line spacing should be +enough for superscripts and subscripts not to look odd. -Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ emphasis_ is rendered in italics._ _It also work the same in [links in italics with _emphasis _in_ emphasis_.](#)_ +Note: _In italics _emphasis_ is rendered as normal text while _emphasis _in_ +emphasis_ is rendered in italics._ _It also work the same in [links in +italics with _emphasis _in_ emphasis_.](#)_ `code` is a different kind of markup that doesn't allow nested markup. -It's possible for two markup elements to appear **next** _to_ each other and have a space, and appear **next**_to_ each other with no space. It doesn't matter **how** _much_ space it was in the source: in this sentence, it was two space characters. And in this one, there is **a** _newline_. +It's possible for two markup elements to appear **next** _to_ each other and +have a space, and appear **next**_to_ each other with no space. It doesn't +matter **how** _much_ space it was in the source: in this sentence, it was +two space characters. And in this one, there is **a** _newline_. This is also true between _non-_`code` markup _and_ `code`. @@ -46,9 +59,23 @@ Code can appear **inside `other` markup**. Its display shouldn't be affected. # Links and references -This is a [link](#). It sends you to the top of this page. Links can have markup inside them: [**bold**](#), [_italics_](#), [_emphasis_](#), [superscript](#), [subscript](#), and [`code`](#). Links can also be nested _[inside](#)_ markup. Links cannot be nested inside each other. This link has no replacement text: [#](#). The text is filled in by odoc. This is a shorthand link: [#](#). The text is also filled in by odoc in this case. - -This is a reference to [`foo`](#val-foo). References can have replacement text: [the value foo](#val-foo). Except for the special lookup support, references are pretty much just like links. The replacement text can have nested styles: [**bold**](#val-foo), [_italic_](#val-foo), [_emphasis_](#val-foo), [superscript](#val-foo), [subscript](#val-foo), and [`code`](#val-foo). It's also possible to surround a reference in a style: **[`foo`](#val-foo)**. References can't be nested inside references, and links and references can't be nested inside each other. +This is a [link](#). It sends you to the top of this page. Links can have +markup inside them: [**bold**](#), [_italics_](#), [_emphasis_](#), +[superscript](#), [subscript](#), and [`code`](#). +Links can also be nested _[inside](#)_ markup. Links cannot be nested inside +each other. This link has no replacement text: [#](#). The text is filled in +by odoc. This is a shorthand link: [#](#). The text is also filled in by odoc +in this case. + +This is a reference to [`foo`](#val-foo). References can have replacement +text: [the value foo](#val-foo). Except for the special lookup support, +references are pretty much just like links. The replacement text can have +nested styles: [**bold**](#val-foo), [_italic_](#val-foo), +[_emphasis_](#val-foo), [superscript](#val-foo), +[subscript](#val-foo), and [`code`](#val-foo). It's also possible +to surround a reference in a style: **[`foo`](#val-foo)**. References can't +be nested inside references, and links and references can't be nested inside +each other. # Preformatted text @@ -85,7 +112,8 @@ The main difference is these don't get syntax highlighting. 2. shorthand numbered list. -- Shorthand list items can span multiple lines, however trying to put two paragraphs into a shorthand list item using a double line break +- Shorthand list items can span multiple lines, however trying to put two + paragraphs into a shorthand list item using a double line break just creates a paragraph outside the list. @@ -126,7 +154,8 @@ The parser supports any ASCII-compatible encoding, in particuλar UTF-8. # Raw HTML -Raw HTML can be as inline elements into sentences. +Raw HTML can be as inline elements +into sentences.
diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md index a13234fd54..e91ef0e152 100644 --- a/test/generators/markdown/Module.md +++ b/test/generators/markdown/Module.md @@ -10,7 +10,9 @@ Foo. > unit -The module needs at least one signature item, otherwise a bug causes the compiler to drop the module comment (above). See [https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701). +The module needs at least one signature item, otherwise a bug causes the +compiler to drop the module comment (above). See +[https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701). diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md index 9fbdebcd09..d9984c3fa4 100644 --- a/test/generators/markdown/Nested.F.md +++ b/test/generators/markdown/Nested.F.md @@ -26,6 +26,7 @@ Some additional comments. ###### type t = -> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) +> [Arg1.t](Nested.F.argument-1-Arg1.md#type-t) +> * [Arg2.t](Nested.F.argument-2-Arg2.md#type-t) Some type. diff --git a/test/generators/markdown/Ocamlary.Aliases.md b/test/generators/markdown/Ocamlary.Aliases.md index 0389bd3eee..df5c994a82 100644 --- a/test/generators/markdown/Ocamlary.Aliases.md +++ b/test/generators/markdown/Ocamlary.Aliases.md @@ -56,7 +56,8 @@ Let's imitate jst's layout. ### include of Foo -Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases.Foo.md). +Just for giggle, let's see what happens when we include +[`Foo`](Ocamlary.Aliases.Foo.md). @@ -92,7 +93,8 @@ Just for giggle, let's see what happens when we include [`Foo`](Ocamlary.Aliases > [A.t](Ocamlary.Aliases.Foo.A.md#type-t) -And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and [`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) +And also, let's refer to [`A.t`](Ocamlary.Aliases.Foo.A.md#type-t) and +[`Foo.B.id`](Ocamlary.Aliases.Foo.B.md#val-id) diff --git a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md index 4af17993a5..de7a6f74d2 100644 --- a/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md +++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md @@ -20,13 +20,15 @@ Module `CanonicalTest.Base_Tests` ###### val foo : -> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float +> [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) ###### val bar : -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) +> 'a [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> 'a +> [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t) diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md index 3fed7cc5d7..df7fd595e0 100644 --- a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md @@ -18,12 +18,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md index 8e0bc94e2f..64ea64131f 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md @@ -20,12 +20,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md index 23ef0effe4..6844d5a9fa 100644 --- a/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md +++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.md @@ -20,7 +20,8 @@ This comment is for `collection`. -###### module [InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) +###### module +[InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md) This comment is for `InnerModuleA`. diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md index a9ce8a56b0..fcabe29698 100644 --- a/test/generators/markdown/Ocamlary.IncludeInclude1.md +++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md @@ -6,8 +6,10 @@ Module `Ocamlary.IncludeInclude1` -###### module type [IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) +###### module type +[IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md) -###### module [IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) +###### module +[IncludeInclude2_M](Ocamlary.IncludeInclude1.IncludeInclude2_M.md) diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md index 564f1a2254..025db37fd6 100644 --- a/test/generators/markdown/Ocamlary.ModuleWithSignature.md +++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md @@ -4,4 +4,5 @@ ModuleWithSignature Module `Ocamlary.ModuleWithSignature` -A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) +A plain module of a signature of +[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md index 54d97c07b3..ed0a568395 100644 --- a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md @@ -18,12 +18,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md index 60dbf22d92..4ebb36848f 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md @@ -20,12 +20,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md index 71b46a375b..4872455f74 100644 --- a/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md +++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.md @@ -20,7 +20,8 @@ This comment is for `collection`. -###### module [InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) +###### module +[InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md) This comment is for `InnerModuleA`. diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index abe61c8e73..e074644d59 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -2,7 +2,8 @@ Ocamlary Module `Ocamlary` -This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: +This is an _interface_ with **all** of the _module system_ features. This +documentation demonstrates: - comment formatting @@ -49,7 +50,8 @@ David Sheets is the author. @author David Sheets -You may find more information about this HTML documentation renderer at [github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary). +You may find more information about this HTML documentation renderer at +[github.com/dsheets/ocamlary](https://github.com/dsheets/ocamlary). This is some verbatim text: @@ -139,11 +141,13 @@ A plain, empty module signature alias of ###### module [ModuleWithSignature](Ocamlary.ModuleWithSignature.md) -A plain module of a signature of [`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) +A plain module of a signature of +[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference) -###### module [ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) +###### module +[ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md) A plain module with an alias signature @@ -161,7 +165,13 @@ There's a signature in a module in this signature. ###### module type [SuperSig](Ocamlary.module-type-SuperSig.md) -For a good time, see [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or [`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md). Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module signature. +For a good time, see +[`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) or +[`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigB.md#subSig) or +[`SuperSig.EmptySig`](Ocamlary.module-type-SuperSig.module-type-EmptySig.md). +Section [Section 9000](#s9000) is also interesting. [EmptySig](#emptySig) is +the section and [`EmptySig`](Ocamlary.module-type-EmptySig.md) is the module +signature. @@ -197,7 +207,8 @@ Unary exception constructor over binary tuple ###### exception EmptySig -[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and [`EmptySig`](#exception-EmptySig) is this exception. +[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and +[`EmptySig`](#exception-EmptySig) is this exception. @@ -213,7 +224,8 @@ Unary exception constructor over binary tuple > 'a -> 'b -[`a_function`](#type-a_function) is this type and [`a_function`](#val-a_function) is the value below. +[`a_function`](#type-a_function) is this type and +[`a_function`](#val-a_function) is the value below. @@ -232,7 +244,8 @@ This is `a_function` with param and return type. ###### val fun_fun_fun : > -> ( ( int, int ) [a_function](#type-a_function), ( unit, unit ) [a_function](#type-a_function) ) [a_function](#type-a_function) +> ( ( int, int ) [a_function](#type-a_function), ( unit, unit ) +> [a_function](#type-a_function) ) [a_function](#type-a_function) @@ -410,7 +423,8 @@ module type of -###### module type [RecollectionModule](Ocamlary.module-type-RecollectionModule.md) +###### module type +[RecollectionModule](Ocamlary.module-type-RecollectionModule.md) @@ -434,7 +448,8 @@ This comment is for `FunctorTypeOf`. -###### module type [IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) +###### module type +[IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md) This comment is for `IncludeModuleType`. @@ -468,6 +483,8 @@ This comment is for `field1`. This comment is for `field2`. +} + This comment is for `record`. This comment is also for `record`. @@ -494,6 +511,8 @@ This comment is also for `record`. `c` is third and mutable +} + ###### type universe_record = { @@ -502,6 +521,8 @@ This comment is also for `record`. > nihilate : 'a. 'a -> unit; +} + ###### type variant = @@ -546,6 +567,8 @@ This comment is also for `variant`. > | `ConstrB of int + ] + This comment is for `poly_variant`. Wow! It was a polymorphic variant! @@ -606,7 +629,8 @@ This comment is for `alias`. ###### type tuple = -> ([alias](#type-alias) * [alias](#type-alias)) * [alias](#type-alias) * ([alias](#type-alias) * [alias](#type-alias)) +> ([alias](#type-alias) * [alias](#type-alias)) * [alias](#type-alias) +> * ([alias](#type-alias) * [alias](#type-alias)) This comment is for `tuple`. @@ -644,6 +668,8 @@ This comment is for `variant_alias`. > field2 : int; +} + This comment is for `record_alias`. @@ -658,6 +684,8 @@ This comment is for `record_alias`. > | `TagC + ] + This comment is for `poly_variant_union`. @@ -668,6 +696,8 @@ This comment is for `poly_variant_union`. > | `TagA of 'a + ] + ###### type ('a, 'b) bin_poly_poly_variant = [ @@ -680,6 +710,8 @@ This comment is for `poly_variant_union`. > | `ConstrB of 'b + ] + ###### type 'a open_poly_variant = @@ -696,7 +728,8 @@ This comment is for `poly_variant_union`. ###### type 'a open_poly_variant_alias = -> 'a [open_poly_variant](#type-open_poly_variant) [open_poly_variant2](#type-open_poly_variant2) +> 'a [open_poly_variant](#type-open_poly_variant) +> [open_poly_variant2](#type-open_poly_variant2) @@ -742,9 +775,12 @@ This comment is for `poly_variant_union`. > | `D of [ `D1 of [ `D1a ] ] + ] + -###### type ('a, 'b) full_gadt_alias = ( 'a, 'b ) [full_gadt](#type-full_gadt) = +###### type ('a, 'b) full_gadt_alias = ( 'a, 'b ) +[full_gadt](#type-full_gadt) = @@ -778,7 +814,8 @@ This comment is for `full_gadt_alias`. -> | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt_alias](#type-partial_gadt_alias) +> | ExistGadtTag : ( 'a -> 'b ) -> 'a +> [partial_gadt_alias](#type-partial_gadt_alias) This comment is for `partial_gadt_alias`. @@ -802,9 +839,11 @@ This comment is for [`Exn_arrow`](#exception-Exn_arrow). > | B_ish of [mutual_constr_b](#type-mutual_constr_b) -This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and [`mutual_constr_b`](#type-mutual_constr_b). +This comment is between [`mutual_constr_a`](#type-mutual_constr_a) and +[`mutual_constr_b`](#type-mutual_constr_b). -This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then [`mutual_constr_b`](#type-mutual_constr_b). +This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then +[`mutual_constr_b`](#type-mutual_constr_b). @@ -820,7 +859,8 @@ This comment is for [`mutual_constr_a`](#type-mutual_constr_a) then [`mutual_con This comment must be here for the next to associate correctly. -This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then [`mutual_constr_a`](#type-mutual_constr_a). +This comment is for [`mutual_constr_b`](#type-mutual_constr_b) then +[`mutual_constr_a`](#type-mutual_constr_a). @@ -1192,16 +1232,18 @@ A brown paper package tied up with string # Trying the {!modules: ...} command. -With ocamldoc, toplevel units will be linked and documented, while submodules will behave as simple references. +With ocamldoc, toplevel units will be linked and documented, while submodules +will behave as simple references. -With odoc, everything should be resolved (and linked) but only toplevel units will be documented. +With odoc, everything should be resolved (and linked) but only toplevel units +will be documented. @[`Dep1.X`](Ocamlary.Dep1.X.md) @[`Ocamlary.IncludeInclude1`](Ocamlary.IncludeInclude1.md) -@[`Ocamlary`]() -This is an _interface_ with **all** of the _module system_ features. This documentation demonstrates: +@[`Ocamlary`]() This is an _interface_ with **all** of the _module system_ +features. This documentation demonstrates: ### Weirder usages involving module types @@ -1215,7 +1257,12 @@ This is an _interface_ with **all** of the _module system_ features. This docume ###### module [CanonicalTest](Ocamlary.CanonicalTest.md) -Some ref to [`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) and [`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id). But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) +Some ref to +[`CanonicalTest.Base_Tests.C.t`](Ocamlary.CanonicalTest.Base_Tests.C.md#type-t) +and +[`CanonicalTest.Base_Tests.L.id`](Ocamlary.CanonicalTest.Base.List.md#val-id). +But also to [`CanonicalTest.Base.List`](Ocamlary.CanonicalTest.Base.List.md) +and [`CanonicalTest.Base.List.t`](Ocamlary.CanonicalTest.Base.List.md#type-t) # Aliases again @@ -1229,7 +1276,8 @@ Let's imitate jst's layout. I can refer to -- `{!section:indexmodules}` : [Trying the {!modules: ...} command.](#indexmodules) +- `{!section:indexmodules}` : [Trying the {!modules: ...} + command.](#indexmodules) - `{!aliases}` : [Aliases again](#aliases) @@ -1237,7 +1285,8 @@ I can refer to But also to things in submodules: -- `{!section:SuperSig.SubSigA.subSig}` : [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{!section:SuperSig.SubSigA.subSig}` : + [`subSig`](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) - `{!Aliases.incl}` : [`incl`](Ocamlary.Aliases.md#incl) @@ -1251,7 +1300,8 @@ And just to make sure we do not mess up: - `{{!aliases}B}` : [B](#aliases) -- `{{!section:SuperSig.SubSigA.subSig}C}` : [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) +- `{{!section:SuperSig.SubSigA.subSig}C}` : + [C](Ocamlary.module-type-SuperSig.module-type-SubSigA.md#subSig) - `{{!Aliases.incl}D}` : [D](Ocamlary.Aliases.md#incl) @@ -1279,16 +1329,20 @@ Here goes: ###### module [Only_a_module](Ocamlary.Only_a_module.md) -- `{!Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!Only_a_module.t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!module-Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!module-Only_a_module.type-t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!module-Only_a_module.type-t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) -- `{!type:Only_a_module.t}` : [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) +- `{!type:Only_a_module.t}` : + [`Only_a_module.t`](Ocamlary.Only_a_module.md#type-t) diff --git a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md index 066b8a008a..888457b937 100644 --- a/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md @@ -20,12 +20,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md index 20ed2ed783..8ba3ae9960 100644 --- a/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md @@ -20,12 +20,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md index d54c480658..7fb5375ddc 100644 --- a/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md @@ -20,12 +20,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md index fed0d24364..4cb1c304e0 100644 --- a/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md @@ -18,12 +18,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md index 011207d5a0..213099c295 100644 --- a/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md @@ -20,12 +20,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md index f06831974c..97726c9f67 100644 --- a/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md +++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md @@ -6,4 +6,5 @@ Module type `Ocamlary.NestedInclude1` -###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) +###### module type +[NestedInclude2](Ocamlary.module-type-NestedInclude1.module-type-NestedInclude2.md) diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md index 23d4364985..8b2ecda941 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md @@ -18,12 +18,14 @@ This comment is for `t`. -###### module [InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) +###### module +[InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md) This comment is for `InnerModuleA'`. -###### module type [InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) +###### module type +[InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md) This comment is for `InnerModuleTypeA'`. diff --git a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md index 3ce0bf479e..c5ae6dad29 100644 --- a/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md +++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md @@ -18,7 +18,8 @@ Module type `Ocamlary.RecollectionModule` -###### module [InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) +###### module +[InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md) This comment is for `InnerModuleA`. diff --git a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md index 2fadb0ac77..2aee21fad4 100644 --- a/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md +++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md @@ -8,4 +8,5 @@ Module `SigForMod.Inner` -###### module type [Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) +###### module type +[Empty](Ocamlary.module-type-SigForMod.Inner.module-type-Empty.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.md index 76a9c9ee27..cc52b8ba66 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md @@ -6,15 +6,18 @@ Module type `Ocamlary.SuperSig` -###### module type [SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) +###### module type +[SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md) -###### module type [SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) +###### module type +[SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md) -###### module type [EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) +###### module type +[EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md) @@ -22,4 +25,5 @@ Module type `Ocamlary.SuperSig` -###### module type [SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) +###### module type +[SuperSig](Ocamlary.module-type-SuperSig.module-type-SuperSig.md) diff --git a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md index adcc45394c..5dd0dd483f 100644 --- a/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md +++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md @@ -14,4 +14,5 @@ Module type `SuperSig.SubSigA` -###### module [SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) +###### module +[SubSigAMod](Ocamlary.module-type-SuperSig.module-type-SubSigA.SubSigAMod.md) diff --git a/test/generators/markdown/Ocamlary.module-type-ToInclude.md b/test/generators/markdown/Ocamlary.module-type-ToInclude.md index 9583e397a3..f4e70e5a10 100644 --- a/test/generators/markdown/Ocamlary.module-type-ToInclude.md +++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md @@ -10,4 +10,5 @@ Module type `Ocamlary.ToInclude` -###### module type [IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) +###### module type +[IncludedB](Ocamlary.module-type-ToInclude.module-type-IncludedB.md) diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 1854ed96a1..43e167bf37 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -42,6 +42,8 @@ _bar_ > a : int; +} + ###### type _ gadt = @@ -64,7 +66,7 @@ foo > a : int; - -> unit [gadt](#type-gadt) +} -> unit [gadt](#type-gadt) @@ -90,6 +92,8 @@ foo bar + ] + ###### type empty_variant = diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index d3e91bbd3b..72b49cd3b8 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -15,3 +15,5 @@ Module type `Recent.PolyS` > | `B + + ] diff --git a/test/generators/markdown/Section.md b/test/generators/markdown/Section.md index b825da564b..10bcca8174 100644 --- a/test/generators/markdown/Section.md +++ b/test/generators/markdown/Section.md @@ -30,4 +30,6 @@ Foo bar. # _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. +But links are impossible thanks to the parser, so we never have trouble +rendering a section title in a table of contents – no link will be nested +inside another link. diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md index f075c038c7..10df64d1f7 100644 --- a/test/generators/markdown/Stop.md +++ b/test/generators/markdown/Stop.md @@ -12,11 +12,17 @@ This test cases exercises stop comments. This is normal commented text. -The next value is `bar`, and it should be missing from the documentation. There is also an entire module, `M`, which should also be hidden. It contains a nested stop comment, but that stop comment should not turn documentation back on in this outer module, because stop comments respect scope. +The next value is `bar`, and it should be missing from the documentation. +There is also an entire module, `M`, which should also be hidden. It contains +a nested stop comment, but that stop comment should not turn documentation +back on in this outer module, because stop comments respect scope. Documentation is on again. -Now, we have a nested module, and it has a stop comment between its two items. We want to see that the first item is displayed, but the second is missing, and the stop comment disables documenation only in that module, and not in this outer module. +Now, we have a nested module, and it has a stop comment between its two +items. We want to see that the first item is displayed, but the second is +missing, and the stop comment disables documenation only in that module, and +not in this outer module. diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index e3580a5319..372865c8f5 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -26,6 +26,8 @@ Module `Stop_dead_link_doc` > field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t); +} + ###### type foo_ = diff --git a/test/generators/markdown/Toplevel_comments.Comments_on_open.md b/test/generators/markdown/Toplevel_comments.Comments_on_open.md index 08bf35d202..6389c8bf65 100644 --- a/test/generators/markdown/Toplevel_comments.Comments_on_open.md +++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md @@ -10,4 +10,5 @@ Module `Toplevel_comments.Comments_on_open` ## Section -Comments attached to open are treated as floating comments. Referencing [Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works +Comments attached to open are treated as floating comments. Referencing +[Section](#sec) [`M.t`](Toplevel_comments.Comments_on_open.M.md#type-t) works diff --git a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md index 5b43ef08b5..40045252ec 100644 --- a/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md +++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md @@ -6,7 +6,8 @@ Module `Toplevel_comments.Ref_in_synopsis` [`t`](#type-t). -This reference should resolve in the context of this module, even when used as a synopsis. +This reference should resolve in the context of this module, even when used +as a synopsis. diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md index fb85045525..79e2bf24f0 100644 --- a/test/generators/markdown/Toplevel_comments.md +++ b/test/generators/markdown/Toplevel_comments.md @@ -2,7 +2,8 @@ Toplevel_comments Module `Toplevel_comments` -A doc comment at the beginning of a module is considered to be that module's doc. +A doc comment at the beginning of a module is considered to be that module's +doc. @@ -24,13 +25,15 @@ Doc of `Include_inline`, part 1. -###### module type [Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) +###### module type +[Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md) Doc of `T`, part 2. -###### module type [Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) +###### module type +[Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md) Doc of `Include_inline_T'`, part 1. diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index f4d781ba8b..b8041f2c8a 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -97,11 +97,14 @@ Some _documentation_. > [pair](#type-pair) > -> > [labeled](#type-labeled) -> -> [higher_order](#type-higher_order) -> +> [higher_order](#type-higher_order) +> -> > ( string -> int ) -> -> (int * float * char * string * char * unit) option -> +> (int * float * char * string * char * unit) +> option -> > [nested_pair](#type-nested_pair) -> -> [arrow](#type-arrow) -> +> [arrow](#type-arrow) +> -> > string -> > [nested_pair](#type-nested_pair) array @@ -113,6 +116,8 @@ Some _documentation_. > a : int; +} + ###### type variant = @@ -149,6 +154,8 @@ _bar_ > a : int; +} + ###### type _ gadt = @@ -209,6 +216,8 @@ _bar_ > e : 'a. 'a; +} + ###### type polymorphic_variant = [ @@ -229,6 +238,8 @@ _bar_ > | `D + ] + ###### type polymorphic_variant_extension = [ @@ -241,6 +252,8 @@ _bar_ > | `E + ] + ###### type nested_polymorphic_variant = [ @@ -249,6 +262,8 @@ _bar_ > | `A of [ `B | `C ] + ] + ###### type private_extenion#row @@ -261,6 +276,8 @@ _bar_ > | [polymorphic_variant](#type-polymorphic_variant) + ] + ###### type object_ = @@ -281,7 +298,9 @@ _bar_ ###### type module_substitution = -> (module [X](Type.module-type-X.md) with type [t](Type.module-type-X.md#type-t) = int and type [u](Type.module-type-X.md#type-u) = unit) +> (module [X](Type.module-type-X.md) with type +> [t](Type.module-type-X.md#type-t) = int and type +> [u](Type.module-type-X.md#type-u) = unit) diff --git a/test/generators/markdown/mld.md b/test/generators/markdown/mld.md index 3e0cb7a46c..a99de7ddc8 100644 --- a/test/generators/markdown/mld.md +++ b/test/generators/markdown/mld.md @@ -2,7 +2,8 @@ mld Mld Page -This is an `.mld` file. It doesn't have an auto-generated title, like modules and other pages generated fully by odoc do. +This is an `.mld` file. It doesn't have an auto-generated title, like modules +and other pages generated fully by odoc do. It will have a TOC generated from section headings. From be8a61595efc3ba22543e8ecc823b4fd63015ba1 Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Tue, 15 Feb 2022 12:14:55 +0300 Subject: [PATCH 36/38] mark up record and variant closing brackets that are blocks --- src/markdown/generator.ml | 12 +++++++++++- test/generators/markdown/Labels.md | 2 ++ test/generators/markdown/Ocamlary.md | 18 ++++++++++++++++++ test/generators/markdown/Recent.md | 6 ++++++ .../markdown/Recent.module-type-PolyS.md | 2 ++ test/generators/markdown/Stop_dead_link_doc.md | 2 ++ test/generators/markdown/Type.md | 14 ++++++++++++++ 7 files changed, 55 insertions(+), 1 deletion(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index d8c1410bec..adedca647a 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -226,7 +226,17 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = in content +++ continue rest | Documented { code; doc; anchor; _ } -> - documented args nesting_level (`D code) doc anchor +++ continue rest + let markedup_bracket = + match rest with + | [] -> noop_block + | d :: _rest' -> ( + match d with + | DocumentedSrc.Code c -> + item_heading nesting_level (source_code c args) + | _ -> noop_block) + in + documented args nesting_level (`D code) doc anchor + +++ markedup_bracket +++ continue rest | Nested { code; doc; anchor; _ } -> documented args nesting_level (`N code) doc anchor +++ continue rest) diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index 43ebb91ab0..8823d56b18 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -102,6 +102,8 @@ Attached to constructor Attached to field +###### } + } Testing that labels can be referenced diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index e074644d59..945b3fdd54 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -483,6 +483,8 @@ This comment is for `field1`. This comment is for `field2`. +###### } + } This comment is for `record`. @@ -511,6 +513,8 @@ This comment is also for `record`. `c` is third and mutable +###### } + } @@ -521,6 +525,8 @@ This comment is also for `record`. > nihilate : 'a. 'a -> unit; +###### } + } @@ -567,6 +573,8 @@ This comment is also for `variant`. > | `ConstrB of int +###### ] + ] This comment is for `poly_variant`. @@ -668,6 +676,8 @@ This comment is for `variant_alias`. > field2 : int; +###### } + } This comment is for `record_alias`. @@ -684,6 +694,8 @@ This comment is for `record_alias`. > | `TagC +###### ] + ] This comment is for `poly_variant_union`. @@ -696,6 +708,8 @@ This comment is for `poly_variant_union`. > | `TagA of 'a +###### ] + ] @@ -710,6 +724,8 @@ This comment is for `poly_variant_union`. > | `ConstrB of 'b +###### ] + ] @@ -775,6 +791,8 @@ This comment is for `poly_variant_union`. > | `D of [ `D1 of [ `D1a ] ] +###### ] + ] diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index 43e167bf37..de58ef9f0c 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -42,6 +42,8 @@ _bar_ > a : int; +######    } + } @@ -66,6 +68,8 @@ foo > a : int; +######    } + } -> unit [gadt](#type-gadt) @@ -92,6 +96,8 @@ foo bar +###### ] + ] diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index 72b49cd3b8..8089e11c9e 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -16,4 +16,6 @@ Module type `Recent.PolyS` > | `B +###### ] + ] diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index 372865c8f5..2eadb7d2a2 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -26,6 +26,8 @@ Module `Stop_dead_link_doc` > field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t); +######    } + } diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index b8041f2c8a..8d84e7fc68 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -116,6 +116,8 @@ Some _documentation_. > a : int; +###### } + } @@ -154,6 +156,8 @@ _bar_ > a : int; +###### } + } @@ -216,6 +220,8 @@ _bar_ > e : 'a. 'a; +###### } + } @@ -238,6 +244,8 @@ _bar_ > | `D +###### ] + ] @@ -252,6 +260,8 @@ _bar_ > | `E +###### ] + ] @@ -262,6 +272,8 @@ _bar_ > | `A of [ `B | `C ] +###### ] + ] @@ -276,6 +288,8 @@ _bar_ > | [polymorphic_variant](#type-polymorphic_variant) +###### ] + ] From ab13bf82d32c803eb4e1cea6405287bfe1e09e8f Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Tue, 15 Feb 2022 12:24:05 +0300 Subject: [PATCH 37/38] remove redundant brackets --- src/markdown/generator.ml | 4 ++-- test/generators/markdown/Labels.md | 2 -- test/generators/markdown/Ocamlary.md | 8 -------- test/generators/markdown/Recent.md | 4 +--- test/generators/markdown/Stop_dead_link_doc.md | 2 -- test/generators/markdown/Type.md | 6 ------ 6 files changed, 3 insertions(+), 23 deletions(-) diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index adedca647a..16f39c927b 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -31,7 +31,7 @@ type args = { base_path : Url.Path.t; generate_links : bool } let rec source_contains_text (s : Source.t) = let inline_contains_text (i : Inline.t) = let check_inline_desc (i : Inline.desc) = - match i with Text ("" | " ") -> false | Text _ | _ -> true + match i with Text ("" | " " | "}" | "]") -> false | Text _ | _ -> true in List.exists (fun { Inline.desc = d; _ } -> check_inline_desc d) i in @@ -229,7 +229,7 @@ let rec documented_src (l : DocumentedSrc.t) args nesting_level = let markedup_bracket = match rest with | [] -> noop_block - | d :: _rest' -> ( + | d :: _ -> ( match d with | DocumentedSrc.Code c -> item_heading nesting_level (source_code c args) diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md index 8823d56b18..26a5a19b74 100644 --- a/test/generators/markdown/Labels.md +++ b/test/generators/markdown/Labels.md @@ -104,8 +104,6 @@ Attached to field ###### } -} - Testing that labels can be referenced - [Attached to unit](#L1) diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index 945b3fdd54..d83f7af1af 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -485,8 +485,6 @@ This comment is for `field2`. ###### } -} - This comment is for `record`. This comment is also for `record`. @@ -515,8 +513,6 @@ This comment is also for `record`. ###### } -} - ###### type universe_record = { @@ -527,8 +523,6 @@ This comment is also for `record`. ###### } -} - ###### type variant = @@ -678,8 +672,6 @@ This comment is for `variant_alias`. ###### } -} - This comment is for `record_alias`. diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index de58ef9f0c..f7fd39ea9e 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -44,8 +44,6 @@ _bar_ ######    } -} - ###### type _ gadt = @@ -70,7 +68,7 @@ foo ######    } -} -> unit [gadt](#type-gadt) + -> unit [gadt](#type-gadt) diff --git a/test/generators/markdown/Stop_dead_link_doc.md b/test/generators/markdown/Stop_dead_link_doc.md index 2eadb7d2a2..6de5649fb2 100644 --- a/test/generators/markdown/Stop_dead_link_doc.md +++ b/test/generators/markdown/Stop_dead_link_doc.md @@ -28,8 +28,6 @@ Module `Stop_dead_link_doc` ######    } -} - ###### type foo_ = diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 8d84e7fc68..27e038f4ab 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -118,8 +118,6 @@ Some _documentation_. ###### } -} - ###### type variant = @@ -158,8 +156,6 @@ _bar_ ###### } -} - ###### type _ gadt = @@ -222,8 +218,6 @@ _bar_ ###### } -} - ###### type polymorphic_variant = [ From 09685558251a403508ecb164fcb7318077baa7be Mon Sep 17 00:00:00 2001 From: lubegasimon Date: Tue, 15 Feb 2022 12:50:20 +0300 Subject: [PATCH 38/38] promote tests after a rebase --- test/generators/markdown/Ocamlary.md | 20 +++++++++---------- test/generators/markdown/Recent.md | 14 ++++++------- .../markdown/Recent.module-type-PolyS.md | 4 ++-- test/generators/markdown/Type.md | 12 +++++------ 4 files changed, 24 insertions(+), 26 deletions(-) diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md index d83f7af1af..3cbf042c78 100644 --- a/test/generators/markdown/Ocamlary.md +++ b/test/generators/markdown/Ocamlary.md @@ -561,11 +561,11 @@ This comment is also for `variant`. -> | `TagA +> | \`TagA -> | `ConstrB of int +> | \`ConstrB of int ###### ] @@ -684,7 +684,7 @@ This comment is for `record_alias`. -> | `TagC +> | \`TagC ###### ] @@ -698,7 +698,7 @@ This comment is for `poly_variant_union`. -> | `TagA of 'a +> | \`TagA of 'a ###### ] @@ -710,11 +710,11 @@ This comment is for `poly_variant_union`. -> | `TagA of 'a +> | \`TagA of 'a -> | `ConstrB of 'b +> | \`ConstrB of 'b ###### ] @@ -769,19 +769,19 @@ This comment is for `poly_variant_union`. -> | `A +> | \`A -> | `B of [ `B1 | `B2 ] +> | \`B of [ \`B1 | \`B2 ] -> | `C +> | \`C -> | `D of [ `D1 of [ `D1a ] ] +> | \`D of [ \`D1 of [ \`D1a ] ] ###### ] diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md index f7fd39ea9e..fc9087421a 100644 --- a/test/generators/markdown/Recent.md +++ b/test/generators/markdown/Recent.md @@ -76,21 +76,21 @@ foo -> | `A +> | \`A -> | `B of int +> | \`B of int -> | `C +> | \`C foo -> | `D +> | \`D bar @@ -116,8 +116,7 @@ bar -######    | X : [< \`X of & 'a & int * float ] -> -[empty_conj](#type-empty_conj) +> | X : [< \`X of & 'a & int * float ] -> [empty_conj](#type-empty_conj) @@ -125,8 +124,7 @@ bar -######    | X : [< \`X of int & [< \`B of int & float ] ] -> -[conj](#type-conj) +> | X : [< \`X of int & [< \`B of int & float ] ] -> [conj](#type-conj) diff --git a/test/generators/markdown/Recent.module-type-PolyS.md b/test/generators/markdown/Recent.module-type-PolyS.md index 8089e11c9e..baf12a0bda 100644 --- a/test/generators/markdown/Recent.module-type-PolyS.md +++ b/test/generators/markdown/Recent.module-type-PolyS.md @@ -10,11 +10,11 @@ Module type `Recent.PolyS` -> | `A +> | \`A -> | `B +> | \`B ###### ] diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md index 27e038f4ab..6c8cdc41cf 100644 --- a/test/generators/markdown/Type.md +++ b/test/generators/markdown/Type.md @@ -224,19 +224,19 @@ _bar_ -> | `A +> | \`A -> | `B of int +> | \`B of int -> | `C of int * unit +> | \`C of int * unit -> | `D +> | \`D ###### ] @@ -252,7 +252,7 @@ _bar_ -> | `E +> | \`E ###### ] @@ -264,7 +264,7 @@ _bar_ -> | `A of [ `B | `C ] +> | \`A of [ \`B | \`C ] ###### ]