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
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/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..16f39c927b
--- /dev/null
+++ b/src/markdown/generator.ml
@@ -0,0 +1,362 @@
+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 =
+  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
+  | `Italic | `Emphasis -> italic
+  | `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
+
+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
+    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_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 =
+    if i >= String.length s then false
+    else
+      match s.[i] with
+      | ' ' -> is_punctuation s (i + 1)
+      | ':' | '=' -> true
+      | _ -> false
+  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.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
+  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
+  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.find is_not_whitespace s with
+      | None -> inline_trim_begin tl
+      | Some i ->
+          let s = String.with_range ~first:i s 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]. *)
+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))
+
+(** 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 (_, s) -> source_code s args
+
+and inline l args = fold_inlines (inline_one args) l
+
+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)
+  | 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 when source_contains_only_text content ->
+      code_span (source_code_to_string content)
+  | Source content -> source_code content args
+  | Raw_markup (_, s) -> text s
+
+let rec block args l = fold_blocks (block_one args) l
+
+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 -> 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
+
+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 -> space ++ inline i args | _ -> noop)
+  in
+  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
+    [nesting_level].
+    {v
+      ######<space><nbsps><space>Text
+    v} *)
+let item_heading nesting_level content =
+  let pre_nbsp =
+    if nesting_level = 0 then noop
+    else text (string_repeat (nesting_level * 2) "\u{A0}") ++ text " "
+    (* Use literal spaces to avoid breaking. *)
+  in
+  heading 6 (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 =
+  match l with
+  | [] -> noop_block
+  | line :: rest -> (
+      let continue r = 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
+            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 +++ continue rest
+          else continue rest
+      | Subpage { content = { title = _; header = _; items; url = _ }; _ } ->
+          let content =
+            if items = [] then paragraph line_break
+            else item items args (nesting_level + 1)
+          in
+          content +++ continue rest
+      | Documented { code; doc; anchor; _ } ->
+          let markedup_bracket =
+            match rest with
+            | [] -> noop_block
+            | d :: _ -> (
+                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)
+
+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 *) ->
+        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
+          | Text s -> text s
+          | _ -> inline code args
+        in
+        quote_block (paragraph (inline' code args))
+    | `N l (* for constructors *) ->
+        let c, rest = take_code l in
+        quote_block (paragraph (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
+  | [] -> noop_block
+  | i :: rest -> (
+      let continue r = item r args nesting_level in
+      match i with
+      | Text b -> blocks (block args b) (continue rest)
+      | Heading { Heading.label; level; title } ->
+          let heading' =
+            let title = inline title args in
+            match label with
+            | Some _ -> heading level title
+            | None -> paragraph title
+          in
+          blocks heading' (continue rest)
+      | Declaration { attr = _; anchor; content; doc } -> (
+          (*
+             Declarations render like this:
+
+             {v
+             <a id="<id>"></a>
+             ###### <nesting_level> <code from content>
+
+             <rest of content, possibly big>
+
+             <doc>
+             v}
+          *)
+          let take_code_from_declaration content =
+            match take_code content with
+            | begin_code, Alternative (Expansion e) :: tl
+              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
+                (begin_code @ e_code, e_tl @ tl)
+            | begin_code, content -> (begin_code, content)
+          in
+          let render_declaration ~anchor ~doc heading content =
+            let anchor =
+              if args.generate_links then
+                let anchor =
+                  match anchor with Some x -> x.Url.Anchor.anchor | None -> ""
+                in
+                paragraph (anchor' anchor)
+              else noop_block
+            in
+            anchor
+            +++ item_heading nesting_level (source_code heading args)
+            +++ content +++ block args 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 =
+                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 ->
+              render_declaration ~anchor ~doc code
+                (documented_src content args nesting_level))
+      | 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 nesting_level
+            else paragraph (source_code summary args)
+          in
+          blocks d (continue rest))
+
+let page ~generate_links { Page.header; items; url; _ } =
+  let args = { base_path = url; generate_links } in
+  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 children =
+    Utils.flatmap ~f:(fun sp -> subpage ~generate_links sp) (Subpages.compute p)
+  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
new file mode 100644
index 0000000000..4ee136c798
--- /dev/null
+++ b/src/markdown/generator.mli
@@ -0,0 +1,4 @@
+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
new file mode 100644
index 0000000000..99c7238cd0
--- /dev/null
+++ b/src/markdown/link.ml
@@ -0,0 +1,37 @@
+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 -> `IfNotLast | _ -> `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 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 = if should_inline url then [] else [ as_filename url ]
diff --git a/src/markdown/markup.ml b/src/markdown/markup.ml
new file mode 100644
index 0000000000..1be4eb4aa8
--- /dev/null
+++ b/src/markdown/markup.ml
@@ -0,0 +1,135 @@
+open Astring
+
+(* What we need in the markdown generator:
+   Special syntaxes:
+   - Pandoc's heading attributes
+*)
+
+type inlines =
+  | String of string
+  | Join of inlines * inlines
+  | Link of string * inlines
+  | Anchor of string
+  | Linebreak
+  | Noop
+  | Space
+
+type blocks =
+  | ConcatB of blocks * blocks
+  | Block of inlines
+  | CodeBlock of inlines
+  | List of list_type * blocks list
+  | Raw_markup of string
+  | Prefixed_block of string * blocks  (** Prefix every lines of blocks. *)
+
+and list_type = Ordered | Unordered
+
+let ordered_list bs = List (Ordered, bs)
+
+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 = Join (left, right)
+
+let blocks above below = ConcatB (above, below)
+
+let ( +++ ) = blocks
+
+let rec text s =
+  match String.cut ~sep:"`" s with
+  | Some (left, right) ->
+      (* Escape backticks. *)
+      String left ++ String "\\`" ++ text right
+  | None -> String s
+
+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 "_"))
+
+let subscript i = Join (String "<sub>", Join (i, String "</sub>"))
+
+let superscript i = Join (String "<sup>", Join (i, String "</sup>"))
+
+let code_span s =
+  let left, right =
+    if String.is_infix ~affix:"`" s then (String "`` ", String " ``")
+    else (String "`", String "`")
+  in
+  Join (left, Join (String s, right))
+
+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 i = CodeBlock i
+
+let quote_block b = Prefixed_block ("> ", b)
+
+let noop_block = Block Noop
+
+let heading level i =
+  let make_hashes n = String.v ~len:n (fun _ -> '#') in
+  let hashes = make_hashes level in
+  Block (String hashes ++ String " " ++ i)
+
+let rec iter_lines f s 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. *)
+let with_prefixed_formatter prefix sink f =
+  let s = Format.asprintf "%t" f in
+  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@]@\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
+  | String s -> Format.fprintf fmt "%s" s
+  | 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 "<a id=\"%s\"></a>" 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 -> Format.fprintf fmt "@[%a@]@\n" pp_inlines i
+  | CodeBlock i -> Format.fprintf fmt "```@\n%a@\n```" pp_inlines i
+  | 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";
+            pp_list (n + 1) rest
+      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
new file mode 100644
index 0000000000..84759b6273
--- /dev/null
+++ b/src/markdown/markup.mli
@@ -0,0 +1,65 @@
+(** 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
+
+val ( ++ ) : inlines -> inlines -> inlines
+(** Renders two inlines one after the other. *)
+
+val text : string -> inlines
+(** An arbitrary string. *)
+
+val space : inlines
+
+val line_break : inlines
+
+val noop : inlines
+(** Nothing. *)
+
+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
+
+(** {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 raw_markup : string -> blocks
+
+val code_span : string -> inlines
+
+val paragraph : inlines -> blocks
+
+val code_block : inlines -> blocks
+
+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. *)
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..d60ae1ff72
--- /dev/null
+++ b/src/odoc/markdown.ml
@@ -0,0 +1,11 @@
+open Odoc_document
+
+type args = { generate_links : bool }
+
+let render { generate_links } (page : Odoc_document.Types.Page.t) :
+    Odoc_document.Renderer.page =
+  Odoc_markdown.Generator.render ~generate_links page
+
+let files_of_url url = Odoc_markdown.Link.files_of_url url
+
+let renderer = { Renderer.name = "markdown"; render; files_of_url }
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/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 @@ <h1>Module <code><span>Bugs_post_406</span></code></h1>
      <a href="#class-type-let_open" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">type</span>  
+       <span class="keyword">type</span> 
       </span>
       <span><a href="Bugs_post_406-class-type-let_open.html">let_open</a>
       </span>
@@ -33,7 +33,7 @@ <h1>Module <code><span>Bugs_post_406</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-let_open'" class="anchored">
      <a href="#class-let_open'" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Bugs_post_406-class-let_open'.html">let_open'</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@ <h1>Module <code><span>Class</span></code></h1>
      <a href="#class-type-empty" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">type</span>  
+       <span class="keyword">type</span> 
       </span><span><a href="Class-class-type-empty.html">empty</a></span>
       <span> = <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
@@ -29,7 +29,7 @@ <h1>Module <code><span>Class</span></code></h1>
      <a href="#class-type-mutually" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">type</span>  
+       <span class="keyword">type</span> 
       </span>
       <span><a href="Class-class-type-mutually.html">mutually</a></span>
       <span> = <span class="keyword">object</span> ... 
@@ -43,7 +43,7 @@ <h1>Module <code><span>Class</span></code></h1>
      <a href="#class-type-recursive" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">type</span>  
+       <span class="keyword">type</span> 
       </span>
       <span><a href="Class-class-type-recursive.html">recursive</a></span>
       <span> = <span class="keyword">object</span> ... 
@@ -55,7 +55,7 @@ <h1>Module <code><span>Class</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-mutually'" class="anchored">
      <a href="#class-mutually'" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Class-class-mutually'.html">mutually'</a></span>
       <span> : <a href="Class-class-type-mutually.html">mutually</a></span>
      </code>
@@ -64,7 +64,7 @@ <h1>Module <code><span>Class</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-recursive'" class="anchored">
      <a href="#class-recursive'" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Class-class-recursive'.html">recursive'</a></span>
       <span> : <a href="Class-class-type-recursive.html">recursive</a></span>
      </code>
@@ -76,7 +76,7 @@ <h1>Module <code><span>Class</span></code></h1>
      <code>
       <span><span class="keyword">class</span> 
        <span class="keyword">type</span> <span class="keyword">virtual</span>
-         
+        
       </span>
       <span><a href="Class-class-type-empty_virtual.html">empty_virtual</a>
       </span>
@@ -91,7 +91,7 @@ <h1>Module <code><span>Class</span></code></h1>
      <a href="#class-empty_virtual'" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">virtual</span>  
+       <span class="keyword">virtual</span> 
       </span>
       <span><a href="Class-class-empty_virtual'.html">empty_virtual'</a>
       </span><span> : <a href="Class-class-type-empty.html">empty</a></span>
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 @@ <h2 id="L2"><a href="#L2" class="anchor"></a>Attached to nothing</h2>
    <div class="odoc-spec">
     <div class="spec class" id="class-c" class="anchored">
      <a href="#class-c" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Labels-class-c.html">c</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
@@ -86,7 +86,7 @@ <h2 id="L2"><a href="#L2" class="anchor"></a>Attached to nothing</h2>
      <a href="#class-type-cs" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">type</span>  
+       <span class="keyword">type</span> 
       </span><span><a href="Labels-class-type-cs.html">cs</a></span>
       <span> = <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@ <h2 id="module-type"><a href="#module-type" class="anchor"></a>Module type
      <a href="#class-z" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">virtual</span>  
+       <span class="keyword">virtual</span> 
       </span><span><a href="Nested-class-z.html">z</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
@@ -82,7 +82,7 @@ <h2 id="module-type"><a href="#module-type" class="anchor"></a>Module type
      <a href="#class-inherits" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">virtual</span>  
+       <span class="keyword">virtual</span> 
       </span><span><a href="Nested-class-inherits.html">inherits</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@
    <div class="odoc-spec">
     <div class="spec class" id="class-c" class="anchored">
      <a href="#class-c" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Ocamlary-Dep1-X-Y-class-c.html">c</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@ <h1>Module type <code><span>Dep1.S</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-c" class="anchored">
      <a href="#class-c" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Ocamlary-Dep1-module-type-S-class-c.html">c</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@ <h1>Module type <code><span>Dep11.S</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-c" class="anchored">
      <a href="#class-c" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Ocamlary-Dep11-module-type-S-class-c.html">c</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@ <h1>Module <code><span>Ocamlary.Dep13</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-c" class="anchored">
      <a href="#class-c" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Ocamlary-Dep13-class-c.html">c</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
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 @@ <h4 id="advanced-type-stuff">
    <div class="odoc-spec">
     <div class="spec class" id="class-empty_class" class="anchored">
      <a href="#class-empty_class" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Ocamlary-class-empty_class.html">empty_class</a></span>
       <span> : <span class="keyword">object</span> ... 
        <span class="keyword">end</span>
@@ -2122,7 +2122,7 @@ <h4 id="advanced-type-stuff">
    <div class="odoc-spec">
     <div class="spec class" id="class-one_method_class" class="anchored">
      <a href="#class-one_method_class" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span>
        <a href="Ocamlary-class-one_method_class.html">one_method_class</a>
       </span>
@@ -2135,7 +2135,7 @@ <h4 id="advanced-type-stuff">
    <div class="odoc-spec">
     <div class="spec class" id="class-two_method_class" class="anchored">
      <a href="#class-two_method_class" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span>
        <a href="Ocamlary-class-two_method_class.html">two_method_class</a>
       </span>
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 @@ <h1>Module <code><span>Toplevel_comments</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-c1" class="anchored">
      <a href="#class-c1" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Toplevel_comments-class-c1.html">c1</a></span>
       <span> : <span>int <span class="arrow">&#45;&gt;</span></span> 
        <span class="keyword">object</span> ... 
@@ -162,7 +162,7 @@ <h1>Module <code><span>Toplevel_comments</span></code></h1>
      <a href="#class-type-ct" class="anchor"></a>
      <code>
       <span><span class="keyword">class</span> 
-       <span class="keyword">type</span>  
+       <span class="keyword">type</span> 
       </span>
       <span><a href="Toplevel_comments-class-type-ct.html">ct</a></span>
       <span> = <span class="keyword">object</span> ... 
@@ -174,7 +174,7 @@ <h1>Module <code><span>Toplevel_comments</span></code></h1>
    <div class="odoc-spec">
     <div class="spec class" id="class-c2" class="anchored">
      <a href="#class-c2" class="anchor"></a>
-     <code><span><span class="keyword">class</span>  </span>
+     <code><span><span class="keyword">class</span> </span>
       <span><a href="Toplevel_comments-class-c2.html">c2</a></span>
       <span> : <a href="Toplevel_comments-class-type-ct.html">ct</a></span>
      </code>
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/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/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/Alias.X.md b/test/generators/markdown/Alias.X.md
new file mode 100644
index 0000000000..898ce2802e
--- /dev/null
+++ b/test/generators/markdown/Alias.X.md
@@ -0,0 +1,14 @@
+Alias
+
+X
+
+Module `Alias.X`
+
+<a id="type-t"></a>
+
+###### type t =
+
+> int
+
+Module Foo__X documentation. This should appear in the documentation for the
+alias to this module 'X'
diff --git a/test/generators/markdown/Alias.md b/test/generators/markdown/Alias.md
new file mode 100644
index 0000000000..33fd92cbd1
--- /dev/null
+++ b/test/generators/markdown/Alias.md
@@ -0,0 +1,7 @@
+Alias
+
+Module `Alias`
+
+<a id="module-X"></a>
+
+###### module [X](Alias.X.md)
diff --git a/test/generators/markdown/Bugs.md b/test/generators/markdown/Bugs.md
new file mode 100644
index 0000000000..ee6dd795d6
--- /dev/null
+++ b/test/generators/markdown/Bugs.md
@@ -0,0 +1,19 @@
+Bugs
+
+Module `Bugs`
+
+<a id="type-opt"></a>
+
+###### type 'a opt =
+
+> 'a option
+
+<a id="val-foo"></a>
+
+###### 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.
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..92edbb87a4
--- /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`
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..d96ddd9b21
--- /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'`
diff --git a/test/generators/markdown/Bugs_post_406.md b/test/generators/markdown/Bugs_post_406.md
new file mode 100644
index 0000000000..9245984a08
--- /dev/null
+++ b/test/generators/markdown/Bugs_post_406.md
@@ -0,0 +1,14 @@
+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
+
+<a id="class-type-let_open"></a>
+
+###### class type [let_open](Bugs_post_406.class-type-let_open.md)
+
+<a id="class-let_open'"></a>
+
+###### 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
new file mode 100644
index 0000000000..9c44f41e09
--- /dev/null
+++ b/test/generators/markdown/Class.class-type-empty.md
@@ -0,0 +1,5 @@
+Class
+
+empty
+
+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
new file mode 100644
index 0000000000..0ac705802e
--- /dev/null
+++ b/test/generators/markdown/Class.class-type-empty_virtual.md
@@ -0,0 +1,5 @@
+Class
+
+empty_virtual
+
+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
new file mode 100644
index 0000000000..1b5564c8bf
--- /dev/null
+++ b/test/generators/markdown/Class.class-type-mutually.md
@@ -0,0 +1,5 @@
+Class
+
+mutually
+
+Class type `Class.mutually`
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..0ce940c8d3
--- /dev/null
+++ b/test/generators/markdown/Class.class-type-polymorphic.md
@@ -0,0 +1,5 @@
+Class
+
+polymorphic
+
+Class type `Class.polymorphic`
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..ff9f483196
--- /dev/null
+++ b/test/generators/markdown/Class.class-type-recursive.md
@@ -0,0 +1,5 @@
+Class
+
+recursive
+
+Class type `Class.recursive`
diff --git a/test/generators/markdown/Class.empty_virtual'.md b/test/generators/markdown/Class.empty_virtual'.md
new file mode 100644
index 0000000000..f4d83f7e34
--- /dev/null
+++ b/test/generators/markdown/Class.empty_virtual'.md
@@ -0,0 +1,5 @@
+Class
+
+empty_virtual'
+
+Class `Class.empty_virtual'`
diff --git a/test/generators/markdown/Class.md b/test/generators/markdown/Class.md
new file mode 100644
index 0000000000..e1d8761c53
--- /dev/null
+++ b/test/generators/markdown/Class.md
@@ -0,0 +1,39 @@
+Class
+
+Module `Class`
+
+<a id="class-type-empty"></a>
+
+###### class type [empty](Class.class-type-empty.md)
+
+<a id="class-type-mutually"></a>
+
+###### class type [mutually](Class.class-type-mutually.md)
+
+<a id="class-type-recursive"></a>
+
+###### class type [recursive](Class.class-type-recursive.md)
+
+<a id="class-mutually'"></a>
+
+###### class [mutually'](Class.mutually'.md)
+
+<a id="class-recursive'"></a>
+
+###### class [recursive'](Class.recursive'.md)
+
+<a id="class-type-empty_virtual"></a>
+
+###### class type virtual [empty_virtual](Class.class-type-empty_virtual.md)
+
+<a id="class-empty_virtual'"></a>
+
+###### class virtual [empty_virtual'](Class.empty_virtual'.md)
+
+<a id="class-type-polymorphic"></a>
+
+###### class type 'a [polymorphic](Class.class-type-polymorphic.md)
+
+<a id="class-polymorphic'"></a>
+
+###### class 'a [polymorphic'](Class.polymorphic'.md)
diff --git a/test/generators/markdown/Class.mutually'.md b/test/generators/markdown/Class.mutually'.md
new file mode 100644
index 0000000000..020c07874d
--- /dev/null
+++ b/test/generators/markdown/Class.mutually'.md
@@ -0,0 +1,5 @@
+Class
+
+mutually'
+
+Class `Class.mutually'`
diff --git a/test/generators/markdown/Class.polymorphic'.md b/test/generators/markdown/Class.polymorphic'.md
new file mode 100644
index 0000000000..e01816e029
--- /dev/null
+++ b/test/generators/markdown/Class.polymorphic'.md
@@ -0,0 +1,5 @@
+Class
+
+polymorphic'
+
+Class `Class.polymorphic'`
diff --git a/test/generators/markdown/Class.recursive'.md b/test/generators/markdown/Class.recursive'.md
new file mode 100644
index 0000000000..03a47c367e
--- /dev/null
+++ b/test/generators/markdown/Class.recursive'.md
@@ -0,0 +1,5 @@
+Class
+
+recursive'
+
+Class `Class.recursive'`
diff --git a/test/generators/markdown/External.md b/test/generators/markdown/External.md
new file mode 100644
index 0000000000..05b5db0fd7
--- /dev/null
+++ b/test/generators/markdown/External.md
@@ -0,0 +1,11 @@
+External
+
+Module `External`
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> unit -> unit
+
+Foo _bar_.
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..1fb180615b
--- /dev/null
+++ b/test/generators/markdown/Functor.F1.argument-1-Arg.md
@@ -0,0 +1,11 @@
+Functor
+
+F1
+
+1-Arg
+
+Parameter `F1.1-Arg`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor.F1.md b/test/generators/markdown/Functor.F1.md
new file mode 100644
index 0000000000..3fdfa3f332
--- /dev/null
+++ b/test/generators/markdown/Functor.F1.md
@@ -0,0 +1,17 @@
+Functor
+
+F1
+
+Module `Functor.F1`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Functor.F1.argument-1-Arg.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### type t
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..c31ca5c063
--- /dev/null
+++ b/test/generators/markdown/Functor.F2.argument-1-Arg.md
@@ -0,0 +1,11 @@
+Functor
+
+F2
+
+1-Arg
+
+Parameter `F2.1-Arg`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor.F2.md b/test/generators/markdown/Functor.F2.md
new file mode 100644
index 0000000000..89d9208f3f
--- /dev/null
+++ b/test/generators/markdown/Functor.F2.md
@@ -0,0 +1,19 @@
+Functor
+
+F2
+
+Module `Functor.F2`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Functor.F2.argument-1-Arg.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### 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..225510152d
--- /dev/null
+++ b/test/generators/markdown/Functor.F3.argument-1-Arg.md
@@ -0,0 +1,11 @@
+Functor
+
+F3
+
+1-Arg
+
+Parameter `F3.1-Arg`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor.F3.md b/test/generators/markdown/Functor.F3.md
new file mode 100644
index 0000000000..4747896ec8
--- /dev/null
+++ b/test/generators/markdown/Functor.F3.md
@@ -0,0 +1,19 @@
+Functor
+
+F3
+
+Module `Functor.F3`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Functor.F3.argument-1-Arg.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### 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..76a905ceff
--- /dev/null
+++ b/test/generators/markdown/Functor.F4.argument-1-Arg.md
@@ -0,0 +1,11 @@
+Functor
+
+F4
+
+1-Arg
+
+Parameter `F4.1-Arg`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor.F4.md b/test/generators/markdown/Functor.F4.md
new file mode 100644
index 0000000000..f6755cd5b2
--- /dev/null
+++ b/test/generators/markdown/Functor.F4.md
@@ -0,0 +1,17 @@
+Functor
+
+F4
+
+Module `Functor.F4`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Functor.F4.argument-1-Arg.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor.F5.md b/test/generators/markdown/Functor.F5.md
new file mode 100644
index 0000000000..702b4abbd1
--- /dev/null
+++ b/test/generators/markdown/Functor.F5.md
@@ -0,0 +1,13 @@
+Functor
+
+F5
+
+Module `Functor.F5`
+
+# Parameters
+
+# Signature
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor.md b/test/generators/markdown/Functor.md
new file mode 100644
index 0000000000..64e5a4d868
--- /dev/null
+++ b/test/generators/markdown/Functor.md
@@ -0,0 +1,31 @@
+Functor
+
+Module `Functor`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Functor.module-type-S.md)
+
+<a id="module-type-S1"></a>
+
+###### module type [S1](Functor.module-type-S1.md)
+
+<a id="module-F1"></a>
+
+###### module [F1](Functor.F1.md)
+
+<a id="module-F2"></a>
+
+###### module [F2](Functor.F2.md)
+
+<a id="module-F3"></a>
+
+###### module [F3](Functor.F3.md)
+
+<a id="module-F4"></a>
+
+###### module [F4](Functor.F4.md)
+
+<a id="module-F5"></a>
+
+###### 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
new file mode 100644
index 0000000000..4f4486848a
--- /dev/null
+++ b/test/generators/markdown/Functor.module-type-S.md
@@ -0,0 +1,9 @@
+Functor
+
+S
+
+Module type `Functor.S`
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..612d8d7f9c
--- /dev/null
+++ b/test/generators/markdown/Functor.module-type-S1.argument-1-_.md
@@ -0,0 +1,11 @@
+Functor
+
+S1
+
+1-_
+
+Parameter `S1.1-_`
+
+<a id="type-t"></a>
+
+###### type t
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..211952936f
--- /dev/null
+++ b/test/generators/markdown/Functor.module-type-S1.md
@@ -0,0 +1,17 @@
+Functor
+
+S1
+
+Module type `Functor.S1`
+
+# Parameters
+
+<a id="argument-1-_"></a>
+
+###### module [_](Functor.module-type-S1.argument-1-_.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### type t
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..13051940d1
--- /dev/null
+++ b/test/generators/markdown/Functor2.X.argument-1-Y.md
@@ -0,0 +1,11 @@
+Functor2
+
+X
+
+1-Y
+
+Parameter `X.1-Y`
+
+<a id="type-t"></a>
+
+###### type t
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..10cb9494c9
--- /dev/null
+++ b/test/generators/markdown/Functor2.X.argument-2-Z.md
@@ -0,0 +1,11 @@
+Functor2
+
+X
+
+2-Z
+
+Parameter `X.2-Z`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Functor2.X.md b/test/generators/markdown/Functor2.X.md
new file mode 100644
index 0000000000..b17ffae163
--- /dev/null
+++ b/test/generators/markdown/Functor2.X.md
@@ -0,0 +1,35 @@
+Functor2
+
+X
+
+Module `Functor2.X`
+
+# Parameters
+
+<a id="argument-1-Y"></a>
+
+###### module [Y](Functor2.X.argument-1-Y.md)
+
+<a id="argument-2-Z"></a>
+
+###### module [Z](Functor2.X.argument-2-Z.md)
+
+# Signature
+
+<a id="type-y_t"></a>
+
+###### type y_t =
+
+> [Y.t](Functor2.X.argument-1-Y.md#type-t)
+
+<a id="type-z_t"></a>
+
+###### type z_t =
+
+> [Z.t](Functor2.X.argument-2-Z.md#type-t)
+
+<a id="type-x_t"></a>
+
+###### 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..d7a05741b4
--- /dev/null
+++ b/test/generators/markdown/Functor2.md
@@ -0,0 +1,15 @@
+Functor2
+
+Module `Functor2`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Functor2.module-type-S.md)
+
+<a id="module-X"></a>
+
+###### module [X](Functor2.X.md)
+
+<a id="module-type-XF"></a>
+
+###### 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
new file mode 100644
index 0000000000..39bfc705a1
--- /dev/null
+++ b/test/generators/markdown/Functor2.module-type-S.md
@@ -0,0 +1,9 @@
+Functor2
+
+S
+
+Module type `Functor2.S`
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..6866b9b635
--- /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`
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..d53ceaa922
--- /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`
+
+<a id="type-t"></a>
+
+###### type t
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..665e93a7da
--- /dev/null
+++ b/test/generators/markdown/Functor2.module-type-XF.md
@@ -0,0 +1,35 @@
+Functor2
+
+XF
+
+Module type `Functor2.XF`
+
+# Parameters
+
+<a id="argument-1-Y"></a>
+
+###### module [Y](Functor2.module-type-XF.argument-1-Y.md)
+
+<a id="argument-2-Z"></a>
+
+###### module [Z](Functor2.module-type-XF.argument-2-Z.md)
+
+# Signature
+
+<a id="type-y_t"></a>
+
+###### type y_t =
+
+> [Y.t](Functor2.module-type-XF.argument-1-Y.md#type-t)
+
+<a id="type-z_t"></a>
+
+###### type z_t =
+
+> [Z.t](Functor2.module-type-XF.argument-2-Z.md#type-t)
+
+<a id="type-x_t"></a>
+
+###### 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..46c19b8ce6
--- /dev/null
+++ b/test/generators/markdown/Include.md
@@ -0,0 +1,51 @@
+Include
+
+Module `Include`
+
+<a id="module-type-Not_inlined"></a>
+
+###### module type [Not_inlined](Include.module-type-Not_inlined.md)
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="module-type-Inlined"></a>
+
+###### module type [Inlined](Include.module-type-Inlined.md)
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="module-type-Not_inlined_and_closed"></a>
+
+###### 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)
+
+<a id="module-type-Not_inlined_and_opened"></a>
+
+###### module type
+[Not_inlined_and_opened](Include.module-type-Not_inlined_and_opened.md)
+
+<a id="type-w"></a>
+
+###### type w
+
+<a id="module-type-Inherent_Module"></a>
+
+###### module type [Inherent_Module](Include.module-type-Inherent_Module.md)
+
+<a id="module-type-Dorminant_Module"></a>
+
+###### module type
+[Dorminant_Module](Include.module-type-Dorminant_Module.md)
+
+<a id="val-a"></a>
+
+###### 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..f9f4f29313
--- /dev/null
+++ b/test/generators/markdown/Include.module-type-Dorminant_Module.md
@@ -0,0 +1,11 @@
+Include
+
+Dorminant_Module
+
+Module type `Include.Dorminant_Module`
+
+<a id="val-a"></a>
+
+###### 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..4e10a48489
--- /dev/null
+++ b/test/generators/markdown/Include.module-type-Inherent_Module.md
@@ -0,0 +1,11 @@
+Include
+
+Inherent_Module
+
+Module type `Include.Inherent_Module`
+
+<a id="val-a"></a>
+
+###### 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..60679c9de3
--- /dev/null
+++ b/test/generators/markdown/Include.module-type-Inlined.md
@@ -0,0 +1,9 @@
+Include
+
+Inlined
+
+Module type `Include.Inlined`
+
+<a id="type-u"></a>
+
+###### type u
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..0c44e1ccb8
--- /dev/null
+++ b/test/generators/markdown/Include.module-type-Not_inlined.md
@@ -0,0 +1,9 @@
+Include
+
+Not_inlined
+
+Module type `Include.Not_inlined`
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..f1ba9dc490
--- /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`
+
+<a id="type-v"></a>
+
+###### 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
new file mode 100644
index 0000000000..5052c458d3
--- /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`
+
+<a id="type-w"></a>
+
+###### type w
diff --git a/test/generators/markdown/Include2.X.md b/test/generators/markdown/Include2.X.md
new file mode 100644
index 0000000000..e20e4ef5e6
--- /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.
+
+<a id="type-t"></a>
+
+###### 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..aff8a6729b
--- /dev/null
+++ b/test/generators/markdown/Include2.Y.md
@@ -0,0 +1,11 @@
+Include2
+
+Y
+
+Module `Include2.Y`
+
+Top-comment of Y.
+
+<a id="type-t"></a>
+
+###### type t
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..fe24c3343b
--- /dev/null
+++ b/test/generators/markdown/Include2.Y_include_doc.md
@@ -0,0 +1,11 @@
+Include2
+
+Y_include_doc
+
+Module `Include2.Y_include_doc`
+
+<a id="type-t"></a>
+
+###### 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..ce0e611349
--- /dev/null
+++ b/test/generators/markdown/Include2.Y_include_synopsis.md
@@ -0,0 +1,14 @@
+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.
+
+<a id="type-t"></a>
+
+###### 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..1feb8a5d95
--- /dev/null
+++ b/test/generators/markdown/Include2.md
@@ -0,0 +1,34 @@
+Include2
+
+Module `Include2`
+
+<a id="module-X"></a>
+
+###### 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.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> int
+
+<a id="module-Y"></a>
+
+###### module [Y](Include2.Y.md)
+
+Top-comment of Y.
+
+<a id="module-Y_include_synopsis"></a>
+
+###### 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.
+
+<a id="module-Y_include_doc"></a>
+
+###### 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
new file mode 100644
index 0000000000..2e8763f431
--- /dev/null
+++ b/test/generators/markdown/Include_sections.md
@@ -0,0 +1,83 @@
+Include_sections
+
+Module `Include_sections`
+
+<a id="module-type-Something"></a>
+
+###### 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.
+
+<a id="val-something"></a>
+
+###### val something :
+
+> unit
+
+# Something 1
+
+foo
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> unit
+
+## Something 2
+
+<a id="val-bar"></a>
+
+###### val bar :
+
+> unit
+
+foo bar
+
+# Something 1-bis
+
+Some text.
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..fd7b849c03
--- /dev/null
+++ b/test/generators/markdown/Include_sections.module-type-Something.md
@@ -0,0 +1,37 @@
+Include_sections
+
+Something
+
+Module type `Include_sections.Something`
+
+A module type.
+
+<a id="val-something"></a>
+
+###### val something :
+
+> unit
+
+# Something 1
+
+foo
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> unit
+
+## Something 2
+
+<a id="val-bar"></a>
+
+###### val bar :
+
+> unit
+
+foo bar
+
+# Something 1-bis
+
+Some text.
diff --git a/test/generators/markdown/Interlude.md b/test/generators/markdown/Interlude.md
new file mode 100644
index 0000000000..03f1df13d4
--- /dev/null
+++ b/test/generators/markdown/Interlude.md
@@ -0,0 +1,49 @@
+Interlude
+
+Module `Interlude`
+
+This is the comment associated to the module.
+
+Some separate stray text at the top of the module.
+
+<a id="val-foo"></a>
+
+###### 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.
+
+<a id="val-bar"></a>
+
+###### val bar :
+
+> unit
+
+Bar.
+
+<a id="val-multiple"></a>
+
+###### val multiple :
+
+> unit
+
+<a id="val-signature"></a>
+
+###### val signature :
+
+> unit
+
+<a id="val-items"></a>
+
+###### val items :
+
+> unit
+
+Stray text at the bottom of the module.
diff --git a/test/generators/markdown/Labels.A.md b/test/generators/markdown/Labels.A.md
new file mode 100644
index 0000000000..6e14db519c
--- /dev/null
+++ b/test/generators/markdown/Labels.A.md
@@ -0,0 +1,7 @@
+Labels
+
+A
+
+Module `Labels.A`
+
+# Attached to module
diff --git a/test/generators/markdown/Labels.c.md b/test/generators/markdown/Labels.c.md
new file mode 100644
index 0000000000..b56e12b938
--- /dev/null
+++ b/test/generators/markdown/Labels.c.md
@@ -0,0 +1,7 @@
+Labels
+
+c
+
+Class `Labels.c`
+
+# Attached to class
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..e61680835c
--- /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
diff --git a/test/generators/markdown/Labels.md b/test/generators/markdown/Labels.md
new file mode 100644
index 0000000000..26a5a19b74
--- /dev/null
+++ b/test/generators/markdown/Labels.md
@@ -0,0 +1,149 @@
+Labels
+
+Module `Labels`
+
+# Attached to unit
+
+# Attached to nothing
+
+<a id="module-A"></a>
+
+###### module [A](Labels.A.md)
+
+<a id="type-t"></a>
+
+###### type t
+
+Attached to type
+
+<a id="val-f"></a>
+
+###### val f :
+
+> [t](#type-t)
+
+Attached to value
+
+<a id="val-e"></a>
+
+###### val e :
+
+> unit -> [t](#type-t)
+
+Attached to external
+
+<a id="module-type-S"></a>
+
+###### module type [S](Labels.module-type-S.md)
+
+<a id="class-c"></a>
+
+###### class [c](Labels.c.md)
+
+<a id="class-type-cs"></a>
+
+###### class type [cs](Labels.class-type-cs.md)
+
+<a id="exception-E"></a>
+
+###### exception E
+
+Attached to exception
+
+<a id="type-x"></a>
+
+###### type x =
+
+> ..
+
+<a id="extension-decl-X"></a>
+
+###### type [x](#type-x) += 
+
+<a id="extension-X"></a>
+
+> | X
+
+Attached to extension
+
+<a id="module-S"></a>
+
+###### module S :=
+
+> [A](Labels.A.md)
+
+Attached to module subst
+
+<a id="type-s"></a>
+
+###### type s :=
+
+> [t](#type-t)
+
+Attached to type subst
+
+<a id="type-u"></a>
+
+###### type u = 
+
+<a id="type-u.A'"></a>
+
+> | A'
+
+Attached to constructor
+
+<a id="type-v"></a>
+
+###### type v = {
+
+<a id="type-v.f"></a>
+
+> 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)
+  
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..8b7baf8aed
--- /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
diff --git a/test/generators/markdown/Markup.X.md b/test/generators/markdown/Markup.X.md
new file mode 100644
index 0000000000..455eb86b2d
--- /dev/null
+++ b/test/generators/markdown/Markup.X.md
@@ -0,0 +1,5 @@
+Markup
+
+X
+
+Module `Markup.X`
diff --git a/test/generators/markdown/Markup.Y.md b/test/generators/markdown/Markup.Y.md
new file mode 100644
index 0000000000..2ee44eaae5
--- /dev/null
+++ b/test/generators/markdown/Markup.Y.md
@@ -0,0 +1,5 @@
+Markup
+
+Y
+
+Module `Markup.Y`
diff --git a/test/generators/markdown/Markup.md b/test/generators/markdown/Markup.md
new file mode 100644
index 0000000000..cc3228217c
--- /dev/null
+++ b/test/generators/markdown/Markup.md
@@ -0,0 +1,216 @@
+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<sup>script</sup>, sub<sub>script</sub>. 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<sup>script</sup>](#), [sub<sub>script</sub>](#), 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<sup>script</sup>](#val-foo),
+[sub<sub>script</sub>](#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 <input type="text" placeholder="inserted"> as inline elements
+into sentences.
+
+
+    <blockquote>
+      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.
+    </blockquote>
+    
+# 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
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> unit
+
+Comments in structure items **support** _markup_, t<sup>o</sup><sub>o</sub>.
+
+Some modules to support references.
+
+<a id="module-X"></a>
+
+###### module [X](Markup.X.md)
+
+<a id="module-Y"></a>
+
+###### module [Y](Markup.Y.md)
diff --git a/test/generators/markdown/Module.M'.md b/test/generators/markdown/Module.M'.md
new file mode 100644
index 0000000000..0a5637bbd0
--- /dev/null
+++ b/test/generators/markdown/Module.M'.md
@@ -0,0 +1,5 @@
+Module
+
+M'
+
+Module `Module.M'`
diff --git a/test/generators/markdown/Module.Mutually.md b/test/generators/markdown/Module.Mutually.md
new file mode 100644
index 0000000000..16688613af
--- /dev/null
+++ b/test/generators/markdown/Module.Mutually.md
@@ -0,0 +1,5 @@
+Module
+
+Mutually
+
+Module `Module.Mutually`
diff --git a/test/generators/markdown/Module.Recursive.md b/test/generators/markdown/Module.Recursive.md
new file mode 100644
index 0000000000..eca3d33962
--- /dev/null
+++ b/test/generators/markdown/Module.Recursive.md
@@ -0,0 +1,5 @@
+Module
+
+Recursive
+
+Module `Module.Recursive`
diff --git a/test/generators/markdown/Module.md b/test/generators/markdown/Module.md
new file mode 100644
index 0000000000..e91ef0e152
--- /dev/null
+++ b/test/generators/markdown/Module.md
@@ -0,0 +1,73 @@
+Module
+
+Module `Module`
+
+Foo.
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> unit
+
+The module needs at least one signature item, otherwise a bug causes the
+compiler to drop the module comment (above). See
+[https://caml.inria.fr/mantis/view.php?id=7701](https://caml.inria.fr/mantis/view.php?id=7701).
+
+<a id="module-type-S"></a>
+
+###### module type [S](Module.module-type-S.md)
+
+<a id="module-type-S1"></a>
+
+###### module type S1
+
+<a id="module-type-S2"></a>
+
+###### module type S2 =
+
+> [S](Module.module-type-S.md)
+
+<a id="module-type-S3"></a>
+
+###### module type [S3](Module.module-type-S3.md)
+
+<a id="module-type-S4"></a>
+
+###### module type [S4](Module.module-type-S4.md)
+
+<a id="module-type-S5"></a>
+
+###### module type [S5](Module.module-type-S5.md)
+
+<a id="type-result"></a>
+
+###### type ('a, 'b) result
+
+<a id="module-type-S6"></a>
+
+###### module type [S6](Module.module-type-S6.md)
+
+<a id="module-M'"></a>
+
+###### module [M'](Module.M'.md)
+
+<a id="module-type-S7"></a>
+
+###### module type [S7](Module.module-type-S7.md)
+
+<a id="module-type-S8"></a>
+
+###### module type [S8](Module.module-type-S8.md)
+
+<a id="module-type-S9"></a>
+
+###### module type [S9](Module.module-type-S9.md)
+
+<a id="module-Mutually"></a>
+
+###### module [Mutually](Module.Mutually.md)
+
+<a id="module-Recursive"></a>
+
+###### 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
new file mode 100644
index 0000000000..88a2ff84ed
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S.M.md
@@ -0,0 +1,7 @@
+Module
+
+S
+
+M
+
+Module `S.M`
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..bc478c65d0
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S.md
@@ -0,0 +1,25 @@
+Module
+
+S
+
+Module type `Module.S`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="type-v"></a>
+
+###### type 'a v
+
+<a id="type-w"></a>
+
+###### type ('a, 'b) w
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..0a6cfc1dd9
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S3.M.md
@@ -0,0 +1,7 @@
+Module
+
+S3
+
+M
+
+Module `S3.M`
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..30ce278b32
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S3.md
@@ -0,0 +1,29 @@
+Module
+
+S3
+
+Module type `Module.S3`
+
+<a id="type-t"></a>
+
+###### type t =
+
+> int
+
+<a id="type-u"></a>
+
+###### type u =
+
+> string
+
+<a id="type-v"></a>
+
+###### type 'a v
+
+<a id="type-w"></a>
+
+###### type ('a, 'b) w
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..953efa4b1a
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S4.M.md
@@ -0,0 +1,7 @@
+Module
+
+S4
+
+M
+
+Module `S4.M`
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..b9f0f65a85
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S4.md
@@ -0,0 +1,21 @@
+Module
+
+S4
+
+Module type `Module.S4`
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="type-v"></a>
+
+###### type 'a v
+
+<a id="type-w"></a>
+
+###### type ('a, 'b) w
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..e7bc465b04
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S5.M.md
@@ -0,0 +1,7 @@
+Module
+
+S5
+
+M
+
+Module `S5.M`
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..db79daa617
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S5.md
@@ -0,0 +1,21 @@
+Module
+
+S5
+
+Module type `Module.S5`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="type-w"></a>
+
+###### type ('a, 'b) w
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..baa9214fd9
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S6.M.md
@@ -0,0 +1,7 @@
+Module
+
+S6
+
+M
+
+Module `S6.M`
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..90e6458ae7
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S6.md
@@ -0,0 +1,21 @@
+Module
+
+S6
+
+Module type `Module.S6`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="type-v"></a>
+
+###### type 'a v
+
+<a id="module-M"></a>
+
+###### module [M](Module.module-type-S6.M.md)
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..6254790100
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S7.md
@@ -0,0 +1,27 @@
+Module
+
+S7
+
+Module type `Module.S7`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="type-v"></a>
+
+###### type 'a v
+
+<a id="type-w"></a>
+
+###### type ('a, 'b) w
+
+<a id="module-M"></a>
+
+###### 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..e7dcfd351b
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S8.md
@@ -0,0 +1,21 @@
+Module
+
+S8
+
+Module type `Module.S8`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="type-v"></a>
+
+###### type 'a v
+
+<a id="type-w"></a>
+
+###### type ('a, 'b) w
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..a5213a069b
--- /dev/null
+++ b/test/generators/markdown/Module.module-type-S9.md
@@ -0,0 +1,5 @@
+Module
+
+S9
+
+Module type `Module.S9`
diff --git a/test/generators/markdown/Module_type_alias.md b/test/generators/markdown/Module_type_alias.md
new file mode 100644
index 0000000000..3b87c2acf5
--- /dev/null
+++ b/test/generators/markdown/Module_type_alias.md
@@ -0,0 +1,33 @@
+Module_type_alias
+
+Module `Module_type_alias`
+
+Module Type Aliases
+
+<a id="module-type-A"></a>
+
+###### module type [A](Module_type_alias.module-type-A.md)
+
+<a id="module-type-B"></a>
+
+###### module type [B](Module_type_alias.module-type-B.md)
+
+<a id="module-type-D"></a>
+
+###### module type D =
+
+> [A](Module_type_alias.module-type-A.md)
+
+<a id="module-type-E"></a>
+
+###### module type [E](Module_type_alias.module-type-E.md)
+
+<a id="module-type-G"></a>
+
+###### module type [G](Module_type_alias.module-type-G.md)
+
+<a id="module-type-I"></a>
+
+###### 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..6ac3e28d94
--- /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`
+
+<a id="type-a"></a>
+
+###### 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
new file mode 100644
index 0000000000..be60e99bfa
--- /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`
+
+<a id="type-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..b875dffb25
--- /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
+
+<a id="argument-1-C"></a>
+
+###### module [C](Module_type_alias.module-type-B.argument-1-C.md)
+
+# Signature
+
+<a id="type-b"></a>
+
+###### 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
new file mode 100644
index 0000000000..a442ee344c
--- /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`
+
+<a id="type-f"></a>
+
+###### 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
new file mode 100644
index 0000000000..dce23843d0
--- /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`
+
+<a id="type-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..8e977c3cdd
--- /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
+
+<a id="argument-1-F"></a>
+
+###### module [F](Module_type_alias.module-type-E.argument-1-F.md)
+
+<a id="argument-2-C"></a>
+
+###### module [C](Module_type_alias.module-type-E.argument-2-C.md)
+
+# Signature
+
+<a id="type-b"></a>
+
+###### 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
new file mode 100644
index 0000000000..f3c717d676
--- /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`
+
+<a id="type-h"></a>
+
+###### 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
new file mode 100644
index 0000000000..6aa8f87a10
--- /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
+
+<a id="argument-1-H"></a>
+
+###### module [H](Module_type_alias.module-type-G.argument-1-H.md)
+
+# Signature
+
+<a id="type-a"></a>
+
+###### type a
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..933b6873e5
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Basic.md
@@ -0,0 +1,29 @@
+Module_type_subst
+
+Basic
+
+Module `Module_type_subst.Basic`
+
+<a id="module-type-u"></a>
+
+###### module type [u](Module_type_subst.Basic.module-type-u.md)
+
+<a id="module-type-with_"></a>
+
+###### module type [with_](Module_type_subst.Basic.module-type-with_.md)
+
+<a id="module-type-u2"></a>
+
+###### module type [u2](Module_type_subst.Basic.module-type-u2.md)
+
+<a id="module-type-with_2"></a>
+
+###### module type [with_2](Module_type_subst.Basic.module-type-with_2.md)
+
+<a id="module-type-a"></a>
+
+###### module type [a](Module_type_subst.Basic.module-type-a.md)
+
+<a id="module-type-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..a629bc86ed
--- /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`
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..9c371ed646
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Basic.module-type-a.md
@@ -0,0 +1,17 @@
+Module_type_subst
+
+Basic
+
+a
+
+Module type `Basic.a`
+
+<a id="module-type-b"></a>
+
+###### module type b =
+
+> [s](Module_type_subst.module-type-s.md)
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..a57798d11e
--- /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`
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..83d9c0a717
--- /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`
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..a7bbdf28bb
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u.md
@@ -0,0 +1,12 @@
+Module_type_subst
+
+Basic
+
+u
+
+Module type `Basic.u`
+
+<a id="module-type-T"></a>
+
+###### 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
new file mode 100644
index 0000000000..9763654545
--- /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`
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..1f4adbef62
--- /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`
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..773fe4a790
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Basic.module-type-u2.md
@@ -0,0 +1,16 @@
+Module_type_subst
+
+Basic
+
+u2
+
+Module type `Basic.u2`
+
+<a id="module-type-T"></a>
+
+###### module type
+[T](Module_type_subst.Basic.module-type-u2.module-type-T.md)
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..2534590734
--- /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`
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..1e0362847b
--- /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_`
+
+<a id="module-type-T"></a>
+
+###### 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..dccb75219c
--- /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`
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..35b820eab2
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Basic.module-type-with_2.md
@@ -0,0 +1,16 @@
+Module_type_subst
+
+Basic
+
+with_2
+
+Module type `Basic.with_2`
+
+<a id="module-type-T"></a>
+
+###### module type
+[T](Module_type_subst.Basic.module-type-with_2.module-type-T.md)
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..35a98ffcfb
--- /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`
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..57fc04908d
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Local.md
@@ -0,0 +1,25 @@
+Module_type_subst
+
+Local
+
+Module `Module_type_subst.Local`
+
+<a id="type-local"></a>
+
+###### type local :=
+
+> int * int
+
+<a id="module-type-local"></a>
+
+###### module type [local](Module_type_subst.Local.module-type-local.md)
+
+<a id="module-type-w"></a>
+
+###### module type w =
+
+> [local](Module_type_subst.Local.module-type-local.md)
+
+<a id="module-type-s"></a>
+
+###### module type [s](Module_type_subst.Local.module-type-s.md)
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..3ddbb6d3cd
--- /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`
+
+<a id="type-t"></a>
+
+###### 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..7778d7a6d6
--- /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`
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..f2f0dc114b
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Nested.md
@@ -0,0 +1,18 @@
+Module_type_subst
+
+Nested
+
+Module `Module_type_subst.Nested`
+
+<a id="module-type-nested"></a>
+
+###### module type [nested](Module_type_subst.Nested.module-type-nested.md)
+
+<a id="module-type-with_"></a>
+
+###### module type [with_](Module_type_subst.Nested.module-type-with_.md)
+
+<a id="module-type-with_subst"></a>
+
+###### 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
new file mode 100644
index 0000000000..00359a252a
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Nested.module-type-nested.N.md
@@ -0,0 +1,14 @@
+Module_type_subst
+
+Nested
+
+nested
+
+N
+
+Module `nested.N`
+
+<a id="module-type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..154cdf7725
--- /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`
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..b6929a6605
--- /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`
+
+<a id="module-N"></a>
+
+###### module [N](Module_type_subst.Nested.module-type-nested.N.md)
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..2114ab6f4f
--- /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`
+
+<a id="module-type-t"></a>
+
+###### 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..d83636da0e
--- /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_`
+
+<a id="module-N"></a>
+
+###### 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
new file mode 100644
index 0000000000..59a3b82f42
--- /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`
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..9e976d74bd
--- /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`
+
+<a id="module-N"></a>
+
+###### 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
new file mode 100644
index 0000000000..61d75d9812
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.md
@@ -0,0 +1,13 @@
+Module_type_subst
+
+Structural
+
+Module `Module_type_subst.Structural`
+
+<a id="module-type-u"></a>
+
+###### module type [u](Module_type_subst.Structural.module-type-u.md)
+
+<a id="module-type-w"></a>
+
+###### 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
new file mode 100644
index 0000000000..6e840523b4
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.md
@@ -0,0 +1,12 @@
+Module_type_subst
+
+Structural
+
+u
+
+Module type `Structural.u`
+
+<a id="module-type-a"></a>
+
+###### 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
new file mode 100644
index 0000000000..c2358be43a
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.md
@@ -0,0 +1,14 @@
+Module_type_subst
+
+Structural
+
+u
+
+a
+
+Module type `u.a`
+
+<a id="module-type-b"></a>
+
+###### 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
new file mode 100644
index 0000000000..ef3efc4589
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.module-type-u.module-type-a.module-type-b.md
@@ -0,0 +1,16 @@
+Module_type_subst
+
+Structural
+
+u
+
+a
+
+b
+
+Module type `a.b`
+
+<a id="module-type-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..8a1a86beba
--- /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`
+
+<a id="type-t"></a>
+
+###### type t = 
+
+<a id="type-t.A"></a>
+
+######    | 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
new file mode 100644
index 0000000000..4202ddbb08
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.md
@@ -0,0 +1,12 @@
+Module_type_subst
+
+Structural
+
+w
+
+Module type `Structural.w`
+
+<a id="module-type-a"></a>
+
+###### 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
new file mode 100644
index 0000000000..c3fcb61c87
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.md
@@ -0,0 +1,14 @@
+Module_type_subst
+
+Structural
+
+w
+
+a
+
+Module type `w.a`
+
+<a id="module-type-b"></a>
+
+###### 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
new file mode 100644
index 0000000000..18830b5608
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.Structural.module-type-w.module-type-a.module-type-b.md
@@ -0,0 +1,16 @@
+Module_type_subst
+
+Structural
+
+w
+
+a
+
+b
+
+Module type `a.b`
+
+<a id="module-type-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..fcbfa92379
--- /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`
+
+<a id="type-t"></a>
+
+###### type t = 
+
+<a id="type-t.A"></a>
+
+######    | A of [t](#type-t)
diff --git a/test/generators/markdown/Module_type_subst.md b/test/generators/markdown/Module_type_subst.md
new file mode 100644
index 0000000000..ba92f01294
--- /dev/null
+++ b/test/generators/markdown/Module_type_subst.md
@@ -0,0 +1,23 @@
+Module_type_subst
+
+Module `Module_type_subst`
+
+<a id="module-Local"></a>
+
+###### module [Local](Module_type_subst.Local.md)
+
+<a id="module-type-s"></a>
+
+###### module type [s](Module_type_subst.module-type-s.md)
+
+<a id="module-Basic"></a>
+
+###### module [Basic](Module_type_subst.Basic.md)
+
+<a id="module-Nested"></a>
+
+###### module [Nested](Module_type_subst.Nested.md)
+
+<a id="module-Structural"></a>
+
+###### 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
new file mode 100644
index 0000000000..f17741e580
--- /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`
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..0eafa35ad3
--- /dev/null
+++ b/test/generators/markdown/Nested.F.argument-1-Arg1.md
@@ -0,0 +1,25 @@
+Nested
+
+F
+
+1-Arg1
+
+Parameter `F.1-Arg1`
+
+# Type
+
+<a id="type-t"></a>
+
+###### type t
+
+Some type.
+
+# Values
+
+<a id="val-y"></a>
+
+###### val y :
+
+> [t](#type-t)
+
+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
new file mode 100644
index 0000000000..c4e567dfa1
--- /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
+
+<a id="type-t"></a>
+
+###### type t
+
+Some type.
diff --git a/test/generators/markdown/Nested.F.md b/test/generators/markdown/Nested.F.md
new file mode 100644
index 0000000000..d9984c3fa4
--- /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
+
+<a id="argument-1-Arg1"></a>
+
+###### module [Arg1](Nested.F.argument-1-Arg1.md)
+
+<a id="argument-2-Arg2"></a>
+
+###### module [Arg2](Nested.F.argument-2-Arg2.md)
+
+# Signature
+
+# Type
+
+<a id="type-t"></a>
+
+###### 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.X.md b/test/generators/markdown/Nested.X.md
new file mode 100644
index 0000000000..d87c983f29
--- /dev/null
+++ b/test/generators/markdown/Nested.X.md
@@ -0,0 +1,27 @@
+Nested
+
+X
+
+Module `Nested.X`
+
+This is module X.
+
+Some additional comments.
+
+# Type
+
+<a id="type-t"></a>
+
+###### type t
+
+Some type.
+
+# Values
+
+<a id="val-x"></a>
+
+###### val x :
+
+> [t](#type-t)
+
+The value of x.
diff --git a/test/generators/markdown/Nested.inherits.md b/test/generators/markdown/Nested.inherits.md
new file mode 100644
index 0000000000..53c10a54c6
--- /dev/null
+++ b/test/generators/markdown/Nested.inherits.md
@@ -0,0 +1,9 @@
+Nested
+
+inherits
+
+Class `Nested.inherits`
+
+<a id=""></a>
+
+###### inherit [z](Nested.z.md)
diff --git a/test/generators/markdown/Nested.md b/test/generators/markdown/Nested.md
new file mode 100644
index 0000000000..a42a9b76bf
--- /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
+
+<a id="module-X"></a>
+
+###### module [X](Nested.X.md)
+
+This is module X.
+
+# Module type
+
+<a id="module-type-Y"></a>
+
+###### module type [Y](Nested.module-type-Y.md)
+
+This is module type Y.
+
+# Functor
+
+<a id="module-F"></a>
+
+###### module [F](Nested.F.md)
+
+This is a functor F.
+
+# Class
+
+<a id="class-z"></a>
+
+###### class virtual [z](Nested.z.md)
+
+This is class z.
+
+<a id="class-inherits"></a>
+
+###### 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
new file mode 100644
index 0000000000..cf2b911e73
--- /dev/null
+++ b/test/generators/markdown/Nested.module-type-Y.md
@@ -0,0 +1,27 @@
+Nested
+
+Y
+
+Module type `Nested.Y`
+
+This is module type Y.
+
+Some additional comments.
+
+# Type
+
+<a id="type-t"></a>
+
+###### type t
+
+Some type.
+
+# Values
+
+<a id="val-y"></a>
+
+###### val y :
+
+> [t](#type-t)
+
+The value of y.
diff --git a/test/generators/markdown/Nested.z.md b/test/generators/markdown/Nested.z.md
new file mode 100644
index 0000000000..0d28a8d38e
--- /dev/null
+++ b/test/generators/markdown/Nested.z.md
@@ -0,0 +1,39 @@
+Nested
+
+z
+
+Class `Nested.z`
+
+This is class z.
+
+Some additional comments.
+
+<a id="val-y"></a>
+
+###### val y :
+
+> int
+
+Some value.
+
+<a id="val-y'"></a>
+
+###### val mutable virtual y' :
+
+> int
+
+# Methods
+
+<a id="method-z"></a>
+
+###### method z :
+
+> int
+
+Some method.
+
+<a id="method-z'"></a>
+
+###### 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..ace7d0c8fd
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.E.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Aliases
+
+E
+
+Module `Aliases.E`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..87d781cb70
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Foo.A.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Aliases
+
+Foo
+
+A
+
+Module `Foo.A`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..2be08e4b19
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Foo.B.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Aliases
+
+Foo
+
+B
+
+Module `Foo.B`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..ea481ca3cd
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Foo.C.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Aliases
+
+Foo
+
+C
+
+Module `Foo.C`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..eae02160e4
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Foo.D.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Aliases
+
+Foo
+
+D
+
+Module `Foo.D`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..24a0c4aa27
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Foo.E.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Aliases
+
+Foo
+
+E
+
+Module `Foo.E`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..d141c490ab
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Foo.md
@@ -0,0 +1,27 @@
+Ocamlary
+
+Aliases
+
+Foo
+
+Module `Aliases.Foo`
+
+<a id="module-A"></a>
+
+###### module [A](Ocamlary.Aliases.Foo.A.md)
+
+<a id="module-B"></a>
+
+###### module [B](Ocamlary.Aliases.Foo.B.md)
+
+<a id="module-C"></a>
+
+###### module [C](Ocamlary.Aliases.Foo.C.md)
+
+<a id="module-D"></a>
+
+###### module [D](Ocamlary.Aliases.Foo.D.md)
+
+<a id="module-E"></a>
+
+###### module [E](Ocamlary.Aliases.Foo.E.md)
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..20bf3b3873
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.P1.Y.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Aliases
+
+P1
+
+Y
+
+Module `P1.Y`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="val-id"></a>
+
+###### 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..79abe97e96
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.P1.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Aliases
+
+P1
+
+Module `Aliases.P1`
+
+<a id="module-Y"></a>
+
+###### module [Y](Ocamlary.Aliases.P1.Y.md)
diff --git a/test/generators/markdown/Ocamlary.Aliases.P2.md b/test/generators/markdown/Ocamlary.Aliases.P2.md
new file mode 100644
index 0000000000..c01a3c4d96
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.P2.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Aliases
+
+P2
+
+Module `Aliases.P2`
+
+<a id="module-Z"></a>
+
+###### 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..caf8037354
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.Std.md
@@ -0,0 +1,37 @@
+Ocamlary
+
+Aliases
+
+Std
+
+Module `Aliases.Std`
+
+<a id="module-A"></a>
+
+###### module A =
+
+> [Foo.A](Ocamlary.Aliases.Foo.A.md)
+
+<a id="module-B"></a>
+
+###### module B =
+
+> [Foo.B](Ocamlary.Aliases.Foo.B.md)
+
+<a id="module-C"></a>
+
+###### module C =
+
+> [Foo.C](Ocamlary.Aliases.Foo.C.md)
+
+<a id="module-D"></a>
+
+###### module D =
+
+> [Foo.D](Ocamlary.Aliases.Foo.D.md)
+
+<a id="module-E"></a>
+
+###### 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..df5c994a82
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Aliases.md
@@ -0,0 +1,129 @@
+Ocamlary
+
+Aliases
+
+Module `Ocamlary.Aliases`
+
+Let's imitate jst's layout.
+
+<a id="module-Foo"></a>
+
+###### module [Foo](Ocamlary.Aliases.Foo.md)
+
+<a id="module-A'"></a>
+
+###### module A' =
+
+> [Foo.A](Ocamlary.Aliases.Foo.A.md)
+
+<a id="type-tata"></a>
+
+###### type tata =
+
+> [Foo.A.t](Ocamlary.Aliases.Foo.A.md#type-t)
+
+<a id="type-tbtb"></a>
+
+###### type tbtb =
+
+> [Foo.B.t](Ocamlary.Aliases.Foo.B.md#type-t)
+
+<a id="type-tete"></a>
+
+###### type tete
+
+<a id="type-tata'"></a>
+
+###### type tata' =
+
+> [A'.t](Ocamlary.Aliases.Foo.A.md#type-t)
+
+<a id="type-tete2"></a>
+
+###### type tete2 =
+
+> [Foo.E.t](Ocamlary.Aliases.Foo.E.md#type-t)
+
+<a id="module-Std"></a>
+
+###### module [Std](Ocamlary.Aliases.Std.md)
+
+<a id="type-stde"></a>
+
+###### 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).
+
+<a id="module-A"></a>
+
+###### module A =
+
+> [Foo.A](Ocamlary.Aliases.Foo.A.md)
+
+<a id="module-B"></a>
+
+###### module B =
+
+> [Foo.B](Ocamlary.Aliases.Foo.B.md)
+
+<a id="module-C"></a>
+
+###### module C =
+
+> [Foo.C](Ocamlary.Aliases.Foo.C.md)
+
+<a id="module-D"></a>
+
+###### module D =
+
+> [Foo.D](Ocamlary.Aliases.Foo.D.md)
+
+<a id="module-E"></a>
+
+###### module [E](Ocamlary.Aliases.E.md)
+
+<a id="type-testa"></a>
+
+###### 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)
+
+<a id="module-P1"></a>
+
+###### module [P1](Ocamlary.Aliases.P1.md)
+
+<a id="module-P2"></a>
+
+###### module [P2](Ocamlary.Aliases.P2.md)
+
+<a id="module-X1"></a>
+
+###### module X1 =
+
+> [P2.Z](Ocamlary.Aliases.P1.Y.md)
+
+<a id="module-X2"></a>
+
+###### module X2 =
+
+> [P2.Z](Ocamlary.Aliases.P1.Y.md)
+
+<a id="type-p1"></a>
+
+###### type p1 =
+
+> [X1.t](Ocamlary.Aliases.P1.Y.md#type-t)
+
+<a id="type-p2"></a>
+
+###### 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..0d5f754ac7
--- /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.
+
+<a id="val-f"></a>
+
+###### 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..98e87d9297
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.List.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+CanonicalTest
+
+Base
+
+List
+
+Module `Base.List`
+
+<a id="type-t"></a>
+
+###### type 'a t
+
+<a id="val-id"></a>
+
+###### 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..7456d001b1
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+CanonicalTest
+
+Base
+
+Module `CanonicalTest.Base`
+
+<a id="module-List"></a>
+
+###### module [List](Ocamlary.CanonicalTest.Base.List.md)
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..81a06fa09a
--- /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`
+
+<a id="type-t"></a>
+
+###### type 'a t
+
+<a id="val-id"></a>
+
+###### 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..de7a6f74d2
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CanonicalTest.Base_Tests.md
@@ -0,0 +1,37 @@
+Ocamlary
+
+CanonicalTest
+
+Base_Tests
+
+Module `CanonicalTest.Base_Tests`
+
+<a id="module-C"></a>
+
+###### module [C](Ocamlary.CanonicalTest.Base_Tests.C.md)
+
+<a id="module-L"></a>
+
+###### module L =
+
+> [Base.List](Ocamlary.CanonicalTest.Base.List.md)
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> int [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t) -> float
+> [L.t](Ocamlary.CanonicalTest.Base.List.md#type-t)
+
+<a id="val-bar"></a>
+
+###### 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 id="val-baz"></a>
+
+###### 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..5199edd9c9
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CanonicalTest.List_modif.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+CanonicalTest
+
+List_modif
+
+Module `CanonicalTest.List_modif`
+
+<a id="type-t"></a>
+
+###### type 'c t =
+
+> 'c [Base.List.t](Ocamlary.CanonicalTest.Base.List.md#type-t)
+
+<a id="val-id"></a>
+
+###### 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..0d9f10b75e
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CanonicalTest.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+CanonicalTest
+
+Module `Ocamlary.CanonicalTest`
+
+<a id="module-Base"></a>
+
+###### module [Base](Ocamlary.CanonicalTest.Base.md)
+
+<a id="module-Base_Tests"></a>
+
+###### module [Base_Tests](Ocamlary.CanonicalTest.Base_Tests.md)
+
+<a id="module-List_modif"></a>
+
+###### 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
new file mode 100644
index 0000000000..0c07f86adc
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+CollectionModule
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+This comment is for `t`.
diff --git a/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md
new file mode 100644
index 0000000000..df7fd595e0
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.md
@@ -0,0 +1,31 @@
+Ocamlary
+
+CollectionModule
+
+InnerModuleA
+
+Module `CollectionModule.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.CollectionModule.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### module type
+[InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+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
new file mode 100644
index 0000000000..579f5327ec
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+CollectionModule
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.CollectionModule.InnerModuleA.InnerModuleA'.md#type-t)
+
+This comment is for `t`.
diff --git a/test/generators/markdown/Ocamlary.CollectionModule.md b/test/generators/markdown/Ocamlary.CollectionModule.md
new file mode 100644
index 0000000000..1ae93f4f70
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.CollectionModule.md
@@ -0,0 +1,31 @@
+Ocamlary
+
+CollectionModule
+
+Module `Ocamlary.CollectionModule`
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.CollectionModule.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.InnerModuleTypeA'](Ocamlary.CollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+This comment is for `InnerModuleTypeA`.
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..99888d067a
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.c.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep1
+
+X
+
+Y
+
+c
+
+Class `Y.c`
+
+<a id="method-m"></a>
+
+###### 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..af01294c8d
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep1.X.Y.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep1
+
+X
+
+Y
+
+Module `X.Y`
+
+<a id="class-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..dcc14a1bcb
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep1.X.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep1
+
+X
+
+Module `Dep1.X`
+
+<a id="module-Y"></a>
+
+###### module [Y](Ocamlary.Dep1.X.Y.md)
diff --git a/test/generators/markdown/Ocamlary.Dep1.md b/test/generators/markdown/Ocamlary.Dep1.md
new file mode 100644
index 0000000000..cf4efa4931
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep1.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep1
+
+Module `Ocamlary.Dep1`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Ocamlary.Dep1.module-type-S.md)
+
+<a id="module-X"></a>
+
+###### module [X](Ocamlary.Dep1.X.md)
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..4941ed0cd5
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.c.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+Dep1
+
+S
+
+c
+
+Class `S.c`
+
+<a id="method-m"></a>
+
+###### 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..c476643fe3
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep1.module-type-S.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep1
+
+S
+
+Module type `Dep1.S`
+
+<a id="class-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..8a3e164b27
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep11.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+Dep11
+
+Module `Ocamlary.Dep11`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Ocamlary.Dep11.module-type-S.md)
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..9adea9048d
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.c.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+Dep11
+
+S
+
+c
+
+Class `S.c`
+
+<a id="method-m"></a>
+
+###### 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..4bfd93a3c3
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep11.module-type-S.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep11
+
+S
+
+Module type `Dep11.S`
+
+<a id="class-c"></a>
+
+###### 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
new file mode 100644
index 0000000000..8c838e5638
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep12.argument-1-Arg.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep12
+
+1-Arg
+
+Parameter `Dep12.1-Arg`
+
+<a id="module-type-S"></a>
+
+###### module type S
diff --git a/test/generators/markdown/Ocamlary.Dep12.md b/test/generators/markdown/Ocamlary.Dep12.md
new file mode 100644
index 0000000000..07a58e1440
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep12.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Dep12
+
+Module `Ocamlary.Dep12`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Ocamlary.Dep12.argument-1-Arg.md)
+
+# Signature
+
+<a id="module-type-T"></a>
+
+###### 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..bba9294892
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep13.c.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep13
+
+c
+
+Class `Dep13.c`
+
+<a id="method-m"></a>
+
+###### 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..9aae84433f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep13.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+Dep13
+
+Module `Ocamlary.Dep13`
+
+<a id="class-c"></a>
+
+###### class [c](Ocamlary.Dep13.c.md)
diff --git a/test/generators/markdown/Ocamlary.Dep2.A.md b/test/generators/markdown/Ocamlary.Dep2.A.md
new file mode 100644
index 0000000000..b50ab08dad
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep2.A.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep2
+
+A
+
+Module `Dep2.A`
+
+<a id="module-Y"></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..8050458429
--- /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`
+
+<a id="module-Y"></a>
+
+###### 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..2a7ebe9516
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep2.argument-1-Arg.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+Dep2
+
+1-Arg
+
+Parameter `Dep2.1-Arg`
+
+<a id="module-type-S"></a>
+
+###### module type S
+
+<a id="module-X"></a>
+
+###### module [X](Ocamlary.Dep2.argument-1-Arg.X.md)
diff --git a/test/generators/markdown/Ocamlary.Dep2.md b/test/generators/markdown/Ocamlary.Dep2.md
new file mode 100644
index 0000000000..095372b534
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep2.md
@@ -0,0 +1,23 @@
+Ocamlary
+
+Dep2
+
+Module `Ocamlary.Dep2`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Ocamlary.Dep2.argument-1-Arg.md)
+
+# Signature
+
+<a id="module-A"></a>
+
+###### module [A](Ocamlary.Dep2.A.md)
+
+<a id="module-B"></a>
+
+###### 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..0aebd3078e
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep3.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+Dep3
+
+Module `Ocamlary.Dep3`
+
+<a id="type-a"></a>
+
+###### type a
diff --git a/test/generators/markdown/Ocamlary.Dep4.X.md b/test/generators/markdown/Ocamlary.Dep4.X.md
new file mode 100644
index 0000000000..559eef0435
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep4.X.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep4
+
+X
+
+Module `Dep4.X`
+
+<a id="type-b"></a>
+
+###### type b
diff --git a/test/generators/markdown/Ocamlary.Dep4.md b/test/generators/markdown/Ocamlary.Dep4.md
new file mode 100644
index 0000000000..8d5a79e7a3
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep4.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep4
+
+Module `Ocamlary.Dep4`
+
+<a id="module-type-T"></a>
+
+###### module type [T](Ocamlary.Dep4.module-type-T.md)
+
+<a id="module-type-S"></a>
+
+###### module type [S](Ocamlary.Dep4.module-type-S.md)
+
+<a id="module-X"></a>
+
+###### 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
new file mode 100644
index 0000000000..692ecaffe5
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.X.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep4
+
+S
+
+X
+
+Module `S.X`
+
+<a id="type-b"></a>
+
+###### 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
new file mode 100644
index 0000000000..8d2b5f5c5e
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.Y.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+Dep4
+
+S
+
+Y
+
+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
new file mode 100644
index 0000000000..3b30c5c8de
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep4.module-type-S.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+Dep4
+
+S
+
+Module type `Dep4.S`
+
+<a id="module-X"></a>
+
+###### module [X](Ocamlary.Dep4.module-type-S.X.md)
+
+<a id="module-Y"></a>
+
+###### 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
new file mode 100644
index 0000000000..cde7880c43
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep4.module-type-T.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep4
+
+T
+
+Module type `Dep4.T`
+
+<a id="type-b"></a>
+
+###### type b
diff --git a/test/generators/markdown/Ocamlary.Dep5.Z.md b/test/generators/markdown/Ocamlary.Dep5.Z.md
new file mode 100644
index 0000000000..2250570ca5
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep5.Z.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Dep5
+
+Z
+
+Module `Dep5.Z`
+
+<a id="module-X"></a>
+
+###### module X :
+
+> [Arg.T](Ocamlary.Dep5.argument-1-Arg.md#module-type-T)
+
+<a id="module-Y"></a>
+
+###### 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..fbc8e3593f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+Dep5
+
+1-Arg
+
+Parameter `Dep5.1-Arg`
+
+<a id="module-type-T"></a>
+
+###### module type T
+
+<a id="module-type-S"></a>
+
+###### module type [S](Ocamlary.Dep5.argument-1-Arg.module-type-S.md)
+
+<a id="module-X"></a>
+
+###### 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..b8b09c001f
--- /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`
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..164768022e
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep5.argument-1-Arg.module-type-S.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Dep5
+
+1-Arg
+
+S
+
+Module type `1-Arg.S`
+
+<a id="module-X"></a>
+
+###### module X :
+
+> [T](Ocamlary.Dep5.argument-1-Arg.md#module-type-T)
+
+<a id="module-Y"></a>
+
+###### 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
new file mode 100644
index 0000000000..eaad110453
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep5.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep5
+
+Module `Ocamlary.Dep5`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Ocamlary.Dep5.argument-1-Arg.md)
+
+# Signature
+
+<a id="module-Z"></a>
+
+###### 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
new file mode 100644
index 0000000000..183fdb76ed
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep6.X.Y.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep6
+
+X
+
+Y
+
+Module `X.Y`
+
+<a id="type-d"></a>
+
+###### type d
diff --git a/test/generators/markdown/Ocamlary.Dep6.X.md b/test/generators/markdown/Ocamlary.Dep6.X.md
new file mode 100644
index 0000000000..3c497b1431
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep6.X.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep6
+
+X
+
+Module `Dep6.X`
+
+<a id="module-type-R"></a>
+
+###### module type R =
+
+> [S](Ocamlary.Dep6.module-type-S.md)
+
+<a id="module-Y"></a>
+
+###### module [Y](Ocamlary.Dep6.X.Y.md)
diff --git a/test/generators/markdown/Ocamlary.Dep6.md b/test/generators/markdown/Ocamlary.Dep6.md
new file mode 100644
index 0000000000..43a79833e3
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep6.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep6
+
+Module `Ocamlary.Dep6`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Ocamlary.Dep6.module-type-S.md)
+
+<a id="module-type-T"></a>
+
+###### module type [T](Ocamlary.Dep6.module-type-T.md)
+
+<a id="module-X"></a>
+
+###### 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
new file mode 100644
index 0000000000..bc34e6fcbf
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep6.module-type-S.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep6
+
+S
+
+Module type `Dep6.S`
+
+<a id="type-d"></a>
+
+###### 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
new file mode 100644
index 0000000000..c1214b411c
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.Y.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+Dep6
+
+T
+
+Y
+
+Module `T.Y`
+
+<a id="type-d"></a>
+
+###### type d
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..c9e3427cba
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep6.module-type-T.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep6
+
+T
+
+Module type `Dep6.T`
+
+<a id="module-type-R"></a>
+
+###### module type R =
+
+> [S](Ocamlary.Dep6.module-type-S.md)
+
+<a id="module-Y"></a>
+
+###### 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
new file mode 100644
index 0000000000..34eaced164
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep7.M.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Dep7
+
+M
+
+Module `Dep7.M`
+
+<a id="module-type-R"></a>
+
+###### module type R =
+
+> [Arg.S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S)
+
+<a id="module-Y"></a>
+
+###### 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..3f71a9a7f9
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.X.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+Dep7
+
+1-Arg
+
+X
+
+Module `1-Arg.X`
+
+<a id="module-type-R"></a>
+
+###### module type R =
+
+> [S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S)
+
+<a id="module-Y"></a>
+
+###### 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..684a0fd5a7
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Dep7
+
+1-Arg
+
+Parameter `Dep7.1-Arg`
+
+<a id="module-type-S"></a>
+
+###### module type S
+
+<a id="module-type-T"></a>
+
+###### module type [T](Ocamlary.Dep7.argument-1-Arg.module-type-T.md)
+
+<a id="module-X"></a>
+
+###### 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
new file mode 100644
index 0000000000..bc3af25b2f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep7.argument-1-Arg.module-type-T.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+Dep7
+
+1-Arg
+
+T
+
+Module type `1-Arg.T`
+
+<a id="module-type-R"></a>
+
+###### module type R =
+
+> [S](Ocamlary.Dep7.argument-1-Arg.md#module-type-S)
+
+<a id="module-Y"></a>
+
+###### 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..284da5267b
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep7.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+Dep7
+
+Module `Ocamlary.Dep7`
+
+# Parameters
+
+<a id="argument-1-Arg"></a>
+
+###### module [Arg](Ocamlary.Dep7.argument-1-Arg.md)
+
+# Signature
+
+<a id="module-M"></a>
+
+###### module [M](Ocamlary.Dep7.M.md)
diff --git a/test/generators/markdown/Ocamlary.Dep8.md b/test/generators/markdown/Ocamlary.Dep8.md
new file mode 100644
index 0000000000..e672846442
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep8.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+Dep8
+
+Module `Ocamlary.Dep8`
+
+<a id="module-type-T"></a>
+
+###### 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
new file mode 100644
index 0000000000..98d6f2b8a6
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep8.module-type-T.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep8
+
+T
+
+Module type `Dep8.T`
+
+<a id="type-t"></a>
+
+###### type t
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..e4bfd93347
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep9.argument-1-X.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep9
+
+1-X
+
+Parameter `Dep9.1-X`
+
+<a id="module-type-T"></a>
+
+###### module type T
diff --git a/test/generators/markdown/Ocamlary.Dep9.md b/test/generators/markdown/Ocamlary.Dep9.md
new file mode 100644
index 0000000000..e332087cd6
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Dep9.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Dep9
+
+Module `Ocamlary.Dep9`
+
+# Parameters
+
+<a id="argument-1-X"></a>
+
+###### module [X](Ocamlary.Dep9.argument-1-X.md)
+
+# Signature
+
+<a id="module-type-T"></a>
+
+###### 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..a22361ec3f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.DoubleInclude1.DoubleInclude2.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+DoubleInclude1
+
+DoubleInclude2
+
+Module `DoubleInclude1.DoubleInclude2`
+
+<a id="type-double_include"></a>
+
+###### type double_include
diff --git a/test/generators/markdown/Ocamlary.DoubleInclude1.md b/test/generators/markdown/Ocamlary.DoubleInclude1.md
new file mode 100644
index 0000000000..bb36a9977f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.DoubleInclude1.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+DoubleInclude1
+
+Module `Ocamlary.DoubleInclude1`
+
+<a id="module-DoubleInclude2"></a>
+
+###### module [DoubleInclude2](Ocamlary.DoubleInclude1.DoubleInclude2.md)
diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md
new file mode 100644
index 0000000000..b5d0e88132
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.DoubleInclude3.DoubleInclude2.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+DoubleInclude3
+
+DoubleInclude2
+
+Module `DoubleInclude3.DoubleInclude2`
+
+<a id="type-double_include"></a>
+
+###### type double_include
diff --git a/test/generators/markdown/Ocamlary.DoubleInclude3.md b/test/generators/markdown/Ocamlary.DoubleInclude3.md
new file mode 100644
index 0000000000..09b2b4ce38
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.DoubleInclude3.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+DoubleInclude3
+
+Module `Ocamlary.DoubleInclude3`
+
+<a id="module-DoubleInclude2"></a>
+
+###### module [DoubleInclude2](Ocamlary.DoubleInclude3.DoubleInclude2.md)
diff --git a/test/generators/markdown/Ocamlary.Empty.md b/test/generators/markdown/Ocamlary.Empty.md
new file mode 100644
index 0000000000..f7412fe119
--- /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.
diff --git a/test/generators/markdown/Ocamlary.ExtMod.md b/test/generators/markdown/Ocamlary.ExtMod.md
new file mode 100644
index 0000000000..c2d25a0082
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.ExtMod.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+ExtMod
+
+Module `Ocamlary.ExtMod`
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ..
+
+<a id="extension-decl-Leisureforce"></a>
+
+###### type [t](#type-t) += 
+
+<a id="extension-Leisureforce"></a>
+
+> | 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
new file mode 100644
index 0000000000..b9ccc62f50
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+FunctorTypeOf
+
+1-Collection
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..64ea64131f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+FunctorTypeOf
+
+1-Collection
+
+InnerModuleA
+
+Module `1-Collection.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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.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..c9b6d06b72
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+FunctorTypeOf
+
+1-Collection
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..6844d5a9fa
--- /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`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module
+[InnerModuleA](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.InnerModuleTypeA'](Ocamlary.FunctorTypeOf.argument-1-Collection.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+This comment is for `InnerModuleTypeA`.
diff --git a/test/generators/markdown/Ocamlary.FunctorTypeOf.md b/test/generators/markdown/Ocamlary.FunctorTypeOf.md
new file mode 100644
index 0000000000..7164387808
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.FunctorTypeOf.md
@@ -0,0 +1,23 @@
+Ocamlary
+
+FunctorTypeOf
+
+Module `Ocamlary.FunctorTypeOf`
+
+This comment is for `FunctorTypeOf`.
+
+# Parameters
+
+<a id="argument-1-Collection"></a>
+
+###### module [Collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [Collection.collection](Ocamlary.FunctorTypeOf.argument-1-Collection.md#type-collection)
+
+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
new file mode 100644
index 0000000000..2437c64596
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.IncludeInclude1.IncludeInclude2_M.md
@@ -0,0 +1,7 @@
+Ocamlary
+
+IncludeInclude1
+
+IncludeInclude2_M
+
+Module `IncludeInclude1.IncludeInclude2_M`
diff --git a/test/generators/markdown/Ocamlary.IncludeInclude1.md b/test/generators/markdown/Ocamlary.IncludeInclude1.md
new file mode 100644
index 0000000000..fcabe29698
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.IncludeInclude1.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+IncludeInclude1
+
+Module `Ocamlary.IncludeInclude1`
+
+<a id="module-type-IncludeInclude2"></a>
+
+###### module type
+[IncludeInclude2](Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md)
+
+<a id="module-IncludeInclude2_M"></a>
+
+###### 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
new file mode 100644
index 0000000000..9cdc665566
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.IncludeInclude1.module-type-IncludeInclude2.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+IncludeInclude1
+
+IncludeInclude2
+
+Module type `IncludeInclude1.IncludeInclude2`
+
+<a id="type-include_include"></a>
+
+###### type include_include
diff --git a/test/generators/markdown/Ocamlary.IncludeInclude2_M.md b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md
new file mode 100644
index 0000000000..c0b22296e7
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.IncludeInclude2_M.md
@@ -0,0 +1,5 @@
+Ocamlary
+
+IncludeInclude2_M
+
+Module `Ocamlary.IncludeInclude2_M`
diff --git a/test/generators/markdown/Ocamlary.IncludedA.md b/test/generators/markdown/Ocamlary.IncludedA.md
new file mode 100644
index 0000000000..d64a057d18
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.IncludedA.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+IncludedA
+
+Module `Ocamlary.IncludedA`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.M.md b/test/generators/markdown/Ocamlary.M.md
new file mode 100644
index 0000000000..067896f835
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.M.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+M
+
+Module `Ocamlary.M`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.ModuleWithSignature.md b/test/generators/markdown/Ocamlary.ModuleWithSignature.md
new file mode 100644
index 0000000000..025db37fd6
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.ModuleWithSignature.md
@@ -0,0 +1,8 @@
+Ocamlary
+
+ModuleWithSignature
+
+Module `Ocamlary.ModuleWithSignature`
+
+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
new file mode 100644
index 0000000000..ae682f4410
--- /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
diff --git a/test/generators/markdown/Ocamlary.One.md b/test/generators/markdown/Ocamlary.One.md
new file mode 100644
index 0000000000..5cf477779f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.One.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+One
+
+Module `Ocamlary.One`
+
+<a id="type-one"></a>
+
+###### type one
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..074814befd
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Only_a_module.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+Only_a_module
+
+Module `Ocamlary.Only_a_module`
+
+<a id="type-t"></a>
+
+###### type t
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..b3ad723c6d
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Recollection
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+This comment is for `t`.
diff --git a/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md
new file mode 100644
index 0000000000..ed0a568395
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.md
@@ -0,0 +1,31 @@
+Ocamlary
+
+Recollection
+
+InnerModuleA
+
+Module `Recollection.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.Recollection.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### module type
+[InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+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
new file mode 100644
index 0000000000..dec86fd5ee
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+Recollection
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.Recollection.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..f5a924fc7d
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+Recollection
+
+1-C
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..4ebb36848f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+Recollection
+
+1-C
+
+InnerModuleA
+
+Module `1-C.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.Recollection.argument-1-C.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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.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..f068446471
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+Recollection
+
+1-C
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.Recollection.argument-1-C.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..4872455f74
--- /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`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module
+[InnerModuleA](Ocamlary.Recollection.argument-1-C.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.argument-1-C.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+This comment is for `InnerModuleTypeA`.
diff --git a/test/generators/markdown/Ocamlary.Recollection.md b/test/generators/markdown/Ocamlary.Recollection.md
new file mode 100644
index 0000000000..f262468474
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.Recollection.md
@@ -0,0 +1,43 @@
+Ocamlary
+
+Recollection
+
+Module `Ocamlary.Recollection`
+
+# Parameters
+
+<a id="argument-1-C"></a>
+
+###### module [C](Ocamlary.Recollection.argument-1-C.md)
+
+# Signature
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection =
+
+> [C.element](Ocamlary.Recollection.argument-1-C.md#type-element) list
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element =
+
+> [C.collection](Ocamlary.Recollection.argument-1-C.md#type-collection)
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.Recollection.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.InnerModuleTypeA'](Ocamlary.Recollection.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+This comment is for `InnerModuleTypeA`.
diff --git a/test/generators/markdown/Ocamlary.With10.md b/test/generators/markdown/Ocamlary.With10.md
new file mode 100644
index 0000000000..3f86b1c480
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With10.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With10
+
+Module `Ocamlary.With10`
+
+<a id="module-type-T"></a>
+
+###### module type [T](Ocamlary.With10.module-type-T.md)
+
+[`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
new file mode 100644
index 0000000000..f389aa16fe
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With10.module-type-T.M.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+With10
+
+T
+
+M
+
+Module `T.M`
+
+<a id="module-type-S"></a>
+
+###### module type S
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..0f4bcff60e
--- /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.
+
+<a id="module-M"></a>
+
+###### module [M](Ocamlary.With10.module-type-T.M.md)
+
+<a id="module-N"></a>
+
+###### 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..6c5793f6e5
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With2.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+With2
+
+Module `Ocamlary.With2`
+
+<a id="module-type-S"></a>
+
+###### 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
new file mode 100644
index 0000000000..993ed60de2
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With2.module-type-S.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With2
+
+S
+
+Module type `With2.S`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.With3.N.md b/test/generators/markdown/Ocamlary.With3.N.md
new file mode 100644
index 0000000000..979c579e4c
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With3.N.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With3
+
+N
+
+Module `With3.N`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.With3.md b/test/generators/markdown/Ocamlary.With3.md
new file mode 100644
index 0000000000..f5c82fa793
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With3.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+With3
+
+Module `Ocamlary.With3`
+
+<a id="module-M"></a>
+
+###### module M =
+
+> [With2](Ocamlary.With2.md)
+
+<a id="module-N"></a>
+
+###### module [N](Ocamlary.With3.N.md)
diff --git a/test/generators/markdown/Ocamlary.With4.N.md b/test/generators/markdown/Ocamlary.With4.N.md
new file mode 100644
index 0000000000..9c9d6f0966
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With4.N.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With4
+
+N
+
+Module `With4.N`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.With4.md b/test/generators/markdown/Ocamlary.With4.md
new file mode 100644
index 0000000000..bd7b6adc08
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With4.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+With4
+
+Module `Ocamlary.With4`
+
+<a id="module-N"></a>
+
+###### module [N](Ocamlary.With4.N.md)
diff --git a/test/generators/markdown/Ocamlary.With5.N.md b/test/generators/markdown/Ocamlary.With5.N.md
new file mode 100644
index 0000000000..8a28e50377
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With5.N.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With5
+
+N
+
+Module `With5.N`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.With5.md b/test/generators/markdown/Ocamlary.With5.md
new file mode 100644
index 0000000000..137341d6df
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With5.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+With5
+
+Module `Ocamlary.With5`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Ocamlary.With5.module-type-S.md)
+
+<a id="module-N"></a>
+
+###### 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
new file mode 100644
index 0000000000..b876e5194a
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With5.module-type-S.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With5
+
+S
+
+Module type `With5.S`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.With6.md b/test/generators/markdown/Ocamlary.With6.md
new file mode 100644
index 0000000000..ab3e48a58b
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With6.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+With6
+
+Module `Ocamlary.With6`
+
+<a id="module-type-T"></a>
+
+###### module type [T](Ocamlary.With6.module-type-T.md)
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..0f731431a4
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With6.module-type-T.M.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+With6
+
+T
+
+M
+
+Module `T.M`
+
+<a id="module-type-S"></a>
+
+###### module type S
+
+<a id="module-N"></a>
+
+###### 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..1691b88d3e
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With6.module-type-T.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With6
+
+T
+
+Module type `With6.T`
+
+<a id="module-M"></a>
+
+###### 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
new file mode 100644
index 0000000000..bd350e9261
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With7.argument-1-X.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With7
+
+1-X
+
+Parameter `With7.1-X`
+
+<a id="module-type-T"></a>
+
+###### module type T
diff --git a/test/generators/markdown/Ocamlary.With7.md b/test/generators/markdown/Ocamlary.With7.md
new file mode 100644
index 0000000000..d57061bf13
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With7.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+With7
+
+Module `Ocamlary.With7`
+
+# Parameters
+
+<a id="argument-1-X"></a>
+
+###### module [X](Ocamlary.With7.argument-1-X.md)
+
+# Signature
+
+<a id="module-type-T"></a>
+
+###### 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..51e82aa01a
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With9.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+With9
+
+Module `Ocamlary.With9`
+
+<a id="module-type-S"></a>
+
+###### 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
new file mode 100644
index 0000000000..2e3adbb33c
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.With9.module-type-S.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With9
+
+S
+
+Module type `With9.S`
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Ocamlary.empty_class.md b/test/generators/markdown/Ocamlary.empty_class.md
new file mode 100644
index 0000000000..f024055dda
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.empty_class.md
@@ -0,0 +1,5 @@
+Ocamlary
+
+empty_class
+
+Class `Ocamlary.empty_class`
diff --git a/test/generators/markdown/Ocamlary.md b/test/generators/markdown/Ocamlary.md
new file mode 100644
index 0000000000..3cbf042c78
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.md
@@ -0,0 +1,1378 @@
+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<sup>2</sup>
+
+Here is some subscript: x<sub>0</sub>
+
+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
+
+<a id="module-Empty"></a>
+
+###### module [Empty](Ocamlary.Empty.md)
+
+A plain, empty module
+
+<a id="module-type-Empty"></a>
+
+###### module type [Empty](Ocamlary.module-type-Empty.md)
+
+An ambiguous, misnamed module type
+
+<a id="module-type-MissingComment"></a>
+
+###### module type [MissingComment](Ocamlary.module-type-MissingComment.md)
+
+An ambiguous, misnamed module type
+
+# Section 9000
+
+<a id="module-EmptyAlias"></a>
+
+###### module EmptyAlias =
+
+> [Empty](Ocamlary.Empty.md)
+
+A plain module alias of `Empty`
+
+### EmptySig
+
+<a id="module-type-EmptySig"></a>
+
+###### module type [EmptySig](Ocamlary.module-type-EmptySig.md)
+
+A plain, empty module signature
+
+<a id="module-type-EmptySigAlias"></a>
+
+###### module type EmptySigAlias =
+
+> [EmptySig](Ocamlary.module-type-EmptySig.md)
+
+A plain, empty module signature alias of
+
+<a id="module-ModuleWithSignature"></a>
+
+###### module [ModuleWithSignature](Ocamlary.ModuleWithSignature.md)
+
+A plain module of a signature of
+[`EmptySig`](Ocamlary.module-type-EmptySig.md) (reference)
+
+<a id="module-ModuleWithSignatureAlias"></a>
+
+###### module
+[ModuleWithSignatureAlias](Ocamlary.ModuleWithSignatureAlias.md)
+
+A plain module with an alias signature
+
+<a id="module-One"></a>
+
+###### module [One](Ocamlary.One.md)
+
+<a id="module-type-SigForMod"></a>
+
+###### module type [SigForMod](Ocamlary.module-type-SigForMod.md)
+
+There's a signature in a module in this signature.
+
+<a id="module-type-SuperSig"></a>
+
+###### 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.
+
+<a id="module-Buffer"></a>
+
+###### module [Buffer](Ocamlary.Buffer.md)
+
+References are resolved after everything, so `{!Buffer.t}` won't resolve.
+
+Some text before exception title.
+
+### Basic exception stuff
+
+After exception title.
+
+<a id="exception-Kaboom"></a>
+
+###### exception Kaboom of unit
+
+Unary exception constructor
+
+<a id="exception-Kablam"></a>
+
+###### exception Kablam of unit * unit
+
+Binary exception constructor
+
+<a id="exception-Kapow"></a>
+
+###### exception Kapow of unit * unit
+
+Unary exception constructor over binary tuple
+
+<a id="exception-EmptySig"></a>
+
+###### exception EmptySig
+
+[`EmptySig`](Ocamlary.module-type-EmptySig.md) is a module and
+[`EmptySig`](#exception-EmptySig) is this exception.
+
+<a id="exception-EmptySigAlias"></a>
+
+###### exception EmptySigAlias
+
+[`EmptySigAlias`](#exception-EmptySigAlias) is this exception.
+
+### Basic type and value stuff with advanced doc comments
+
+<a id="type-a_function"></a>
+
+###### type ('a, 'b) a_function =
+
+> 'a -> 'b
+
+[`a_function`](#type-a_function) is this type and
+[`a_function`](#val-a_function) is the value below.
+
+<a id="val-a_function"></a>
+
+###### val a_function :
+
+> x:int -> int
+
+This is `a_function` with param and return type.
+
+@parameter x
+
+@returns
+
+<a id="val-fun_fun_fun"></a>
+
+###### val fun_fun_fun :
+
+> 
+>   ( ( int, int ) [a_function](#type-a_function), ( unit, unit )
+> [a_function](#type-a_function) ) [a_function](#type-a_function)
+
+<a id="val-fun_maybe"></a>
+
+###### val fun_maybe :
+
+> ?yes:unit -> unit -> int
+
+<a id="val-not_found"></a>
+
+###### val not_found :
+
+> unit -> unit
+
+@raises Not_found
+
+<a id="val-ocaml_org"></a>
+
+###### val ocaml_org :
+
+> string
+
+@see [http://ocaml.org/](http://ocaml.org/)
+
+<a id="val-some_file"></a>
+
+###### val some_file :
+
+> string
+
+@see `some_file`
+
+<a id="val-some_doc"></a>
+
+###### val some_doc :
+
+> string
+
+@see some_doc
+
+<a id="val-since_mesozoic"></a>
+
+###### val since_mesozoic :
+
+> unit
+
+This value was introduced in the Mesozoic era.
+
+@since mesozoic
+
+<a id="val-changing"></a>
+
+###### val changing :
+
+> unit
+
+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
+
+<a id="val-(~-)"></a>
+
+###### val (~-) :
+
+> unit
+
+<a id="val-(!)"></a>
+
+###### val (!) :
+
+> unit
+
+<a id="val-(@)"></a>
+
+###### val (@) :
+
+> unit
+
+<a id="val-($)"></a>
+
+###### val ($) :
+
+> unit
+
+<a id="val-(%)"></a>
+
+###### val (%) :
+
+> unit
+
+<a id="val-(&)"></a>
+
+###### val (&) :
+
+> unit
+
+<a id="val-(*)"></a>
+
+###### val (*) :
+
+> unit
+
+<a id="val-(-)"></a>
+
+###### val (-) :
+
+> unit
+
+<a id="val-(+)"></a>
+
+###### val (+) :
+
+> unit
+
+<a id="val-(-?)"></a>
+
+###### val (-?) :
+
+> unit
+
+<a id="val-(/)"></a>
+
+###### val (/) :
+
+> unit
+
+<a id="val-(:=)"></a>
+
+###### val (:=) :
+
+> unit
+
+<a id="val-(=)"></a>
+
+###### val (=) :
+
+> unit
+
+<a id="val-(land)"></a>
+
+###### val (land) :
+
+> unit
+
+### Advanced Module Stuff
+
+<a id="module-CollectionModule"></a>
+
+###### module [CollectionModule](Ocamlary.CollectionModule.md)
+
+This comment is for `CollectionModule`.
+
+<a id="module-type-COLLECTION"></a>
+
+###### module type [COLLECTION](Ocamlary.module-type-COLLECTION.md)
+
+module type of
+
+<a id="module-Recollection"></a>
+
+###### module [Recollection](Ocamlary.Recollection.md)
+
+<a id="module-type-MMM"></a>
+
+###### module type [MMM](Ocamlary.module-type-MMM.md)
+
+<a id="module-type-RECOLLECTION"></a>
+
+###### module type [RECOLLECTION](Ocamlary.module-type-RECOLLECTION.md)
+
+<a id="module-type-RecollectionModule"></a>
+
+###### module type
+[RecollectionModule](Ocamlary.module-type-RecollectionModule.md)
+
+<a id="module-type-A"></a>
+
+###### module type [A](Ocamlary.module-type-A.md)
+
+<a id="module-type-B"></a>
+
+###### module type [B](Ocamlary.module-type-B.md)
+
+<a id="module-type-C"></a>
+
+###### module type [C](Ocamlary.module-type-C.md)
+
+This module type includes two signatures.
+
+<a id="module-FunctorTypeOf"></a>
+
+###### module [FunctorTypeOf](Ocamlary.FunctorTypeOf.md)
+
+This comment is for `FunctorTypeOf`.
+
+<a id="module-type-IncludeModuleType"></a>
+
+###### module type
+[IncludeModuleType](Ocamlary.module-type-IncludeModuleType.md)
+
+This comment is for `IncludeModuleType`.
+
+<a id="module-type-ToInclude"></a>
+
+###### module type [ToInclude](Ocamlary.module-type-ToInclude.md)
+
+<a id="module-IncludedA"></a>
+
+###### module [IncludedA](Ocamlary.IncludedA.md)
+
+<a id="module-type-IncludedB"></a>
+
+###### module type [IncludedB](Ocamlary.module-type-IncludedB.md)
+
+### Advanced Type Stuff
+
+<a id="type-record"></a>
+
+###### type record = {
+
+<a id="type-record.field1"></a>
+
+> field1 : int;
+
+This comment is for `field1`.
+
+<a id="type-record.field2"></a>
+
+> field2 : int;
+
+This comment is for `field2`.
+
+###### }
+
+This comment is for `record`.
+
+This comment is also for `record`.
+
+<a id="type-mutable_record"></a>
+
+###### type mutable_record = {
+
+<a id="type-mutable_record.a"></a>
+
+> mutable a : int;
+
+`a` is first and mutable
+
+<a id="type-mutable_record.b"></a>
+
+> b : unit;
+
+`b` is second and immutable
+
+<a id="type-mutable_record.c"></a>
+
+> mutable c : int;
+
+`c` is third and mutable
+
+###### }
+
+<a id="type-universe_record"></a>
+
+###### type universe_record = {
+
+<a id="type-universe_record.nihilate"></a>
+
+> nihilate : 'a. 'a -> unit;
+
+###### }
+
+<a id="type-variant"></a>
+
+###### type variant = 
+
+<a id="type-variant.TagA"></a>
+
+> | TagA
+
+This comment is for `TagA`.
+
+<a id="type-variant.ConstrB"></a>
+
+> | ConstrB of int
+
+This comment is for `ConstrB`.
+
+<a id="type-variant.ConstrC"></a>
+
+> | ConstrC of int * int
+
+This comment is for binary `ConstrC`.
+
+<a id="type-variant.ConstrD"></a>
+
+> | ConstrD of int * int
+
+This comment is for unary `ConstrD` of binary tuple.
+
+This comment is for `variant`.
+
+This comment is also for `variant`.
+
+<a id="type-poly_variant"></a>
+
+###### type poly_variant = [ 
+
+<a id="type-poly_variant.TagA"></a>
+
+> | \`TagA
+
+<a id="type-poly_variant.ConstrB"></a>
+
+> | \`ConstrB of int
+
+######  ]
+
+ ]
+
+This comment is for `poly_variant`.
+
+Wow! It was a polymorphic variant!
+
+<a id="type-full_gadt"></a>
+
+###### type (_, _) full_gadt = 
+
+<a id="type-full_gadt.Tag"></a>
+
+> | Tag : ( unit, unit ) [full_gadt](#type-full_gadt)
+
+<a id="type-full_gadt.First"></a>
+
+> | First : 'a -> ( 'a, unit ) [full_gadt](#type-full_gadt)
+
+<a id="type-full_gadt.Second"></a>
+
+> | Second : 'a -> ( unit, 'a ) [full_gadt](#type-full_gadt)
+
+<a id="type-full_gadt.Exist"></a>
+
+> | Exist : 'a * 'b -> ( 'b, unit ) [full_gadt](#type-full_gadt)
+
+This comment is for `full_gadt`.
+
+Wow! It was a GADT!
+
+<a id="type-partial_gadt"></a>
+
+###### type 'a partial_gadt = 
+
+<a id="type-partial_gadt.AscribeTag"></a>
+
+> | AscribeTag : 'a [partial_gadt](#type-partial_gadt)
+
+<a id="type-partial_gadt.OfTag"></a>
+
+> | OfTag of 'a [partial_gadt](#type-partial_gadt)
+
+<a id="type-partial_gadt.ExistGadtTag"></a>
+
+> | ExistGadtTag : ( 'a -> 'b ) -> 'a [partial_gadt](#type-partial_gadt)
+
+This comment is for `partial_gadt`.
+
+Wow! It was a mixed GADT!
+
+<a id="type-alias"></a>
+
+###### type alias =
+
+> [variant](#type-variant)
+
+This comment is for `alias`.
+
+<a id="type-tuple"></a>
+
+###### type tuple =
+
+> ([alias](#type-alias) * [alias](#type-alias)) * [alias](#type-alias)
+> * ([alias](#type-alias) * [alias](#type-alias))
+
+This comment is for `tuple`.
+
+<a id="type-variant_alias"></a>
+
+###### type variant_alias = [variant](#type-variant) = 
+
+<a id="type-variant_alias.TagA"></a>
+
+> | TagA
+
+<a id="type-variant_alias.ConstrB"></a>
+
+> | ConstrB of int
+
+<a id="type-variant_alias.ConstrC"></a>
+
+> | ConstrC of int * int
+
+<a id="type-variant_alias.ConstrD"></a>
+
+> | ConstrD of int * int
+
+This comment is for `variant_alias`.
+
+<a id="type-record_alias"></a>
+
+###### type record_alias = [record](#type-record) = {
+
+<a id="type-record_alias.field1"></a>
+
+> field1 : int;
+
+<a id="type-record_alias.field2"></a>
+
+> field2 : int;
+
+###### }
+
+This comment is for `record_alias`.
+
+<a id="type-poly_variant_union"></a>
+
+###### type poly_variant_union = [ 
+
+<a id="type-poly_variant_union.poly_variant"></a>
+
+> | [poly_variant](#type-poly_variant)
+
+<a id="type-poly_variant_union.TagC"></a>
+
+> | \`TagC
+
+######  ]
+
+ ]
+
+This comment is for `poly_variant_union`.
+
+<a id="type-poly_poly_variant"></a>
+
+###### type 'a poly_poly_variant = [ 
+
+<a id="type-poly_poly_variant.TagA"></a>
+
+> | \`TagA of 'a
+
+######  ]
+
+ ]
+
+<a id="type-bin_poly_poly_variant"></a>
+
+###### type ('a, 'b) bin_poly_poly_variant = [ 
+
+<a id="type-bin_poly_poly_variant.TagA"></a>
+
+> | \`TagA of 'a
+
+<a id="type-bin_poly_poly_variant.ConstrB"></a>
+
+> | \`ConstrB of 'b
+
+######  ]
+
+ ]
+
+<a id="type-open_poly_variant"></a>
+
+###### type 'a open_poly_variant =
+
+> [> \`TagA ] as 'a
+
+<a id="type-open_poly_variant2"></a>
+
+###### type 'a open_poly_variant2 =
+
+> [> \`ConstrB of int ] as 'a
+
+<a id="type-open_poly_variant_alias"></a>
+
+###### type 'a open_poly_variant_alias =
+
+> 'a [open_poly_variant](#type-open_poly_variant)
+> [open_poly_variant2](#type-open_poly_variant2)
+
+<a id="type-poly_fun"></a>
+
+###### type 'a poly_fun =
+
+> [> \`ConstrB of int ] as 'a -> 'a
+
+<a id="type-poly_fun_constraint"></a>
+
+###### type 'a poly_fun_constraint =
+
+> 'a -> 'a constraint 'a = [> \`TagA ]
+
+<a id="type-closed_poly_variant"></a>
+
+###### type 'a closed_poly_variant =
+
+> [< \`One | \`Two ] as 'a
+
+<a id="type-clopen_poly_variant"></a>
+
+###### type 'a clopen_poly_variant =
+
+> [< \`One | \`Two of int | \`Three Two Three ] as 'a
+
+<a id="type-nested_poly_variant"></a>
+
+###### type nested_poly_variant = [ 
+
+<a id="type-nested_poly_variant.A"></a>
+
+> | \`A
+
+<a id="type-nested_poly_variant.B"></a>
+
+> | \`B of [ \`B1 | \`B2 ]
+
+<a id="type-nested_poly_variant.C"></a>
+
+> | \`C
+
+<a id="type-nested_poly_variant.D"></a>
+
+> | \`D of [ \`D1 of [ \`D1a ] ]
+
+######  ]
+
+ ]
+
+<a id="type-full_gadt_alias"></a>
+
+###### type ('a, 'b) full_gadt_alias = ( 'a, 'b )
+[full_gadt](#type-full_gadt) = 
+
+<a id="type-full_gadt_alias.Tag"></a>
+
+> | Tag : ( unit, unit ) [full_gadt_alias](#type-full_gadt_alias)
+
+<a id="type-full_gadt_alias.First"></a>
+
+> | First : 'a -> ( 'a, unit ) [full_gadt_alias](#type-full_gadt_alias)
+
+<a id="type-full_gadt_alias.Second"></a>
+
+> | Second : 'a -> ( unit, 'a ) [full_gadt_alias](#type-full_gadt_alias)
+
+<a id="type-full_gadt_alias.Exist"></a>
+
+> | Exist : 'a * 'b -> ( 'b, unit ) [full_gadt_alias](#type-full_gadt_alias)
+
+This comment is for `full_gadt_alias`.
+
+<a id="type-partial_gadt_alias"></a>
+
+###### type 'a partial_gadt_alias = 'a [partial_gadt](#type-partial_gadt) = 
+
+<a id="type-partial_gadt_alias.AscribeTag"></a>
+
+> | AscribeTag : 'a [partial_gadt_alias](#type-partial_gadt_alias)
+
+<a id="type-partial_gadt_alias.OfTag"></a>
+
+> | OfTag of 'a [partial_gadt_alias](#type-partial_gadt_alias)
+
+<a id="type-partial_gadt_alias.ExistGadtTag"></a>
+
+> | ExistGadtTag : ( 'a -> 'b ) -> 'a
+> [partial_gadt_alias](#type-partial_gadt_alias)
+
+This comment is for `partial_gadt_alias`.
+
+<a id="exception-Exn_arrow"></a>
+
+###### exception Exn_arrow :
+
+> unit -> exn
+
+This comment is for [`Exn_arrow`](#exception-Exn_arrow).
+
+<a id="type-mutual_constr_a"></a>
+
+###### type mutual_constr_a = 
+
+<a id="type-mutual_constr_a.A"></a>
+
+> | A
+
+<a id="type-mutual_constr_a.B_ish"></a>
+
+> | 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 for [`mutual_constr_a`](#type-mutual_constr_a) then
+[`mutual_constr_b`](#type-mutual_constr_b).
+
+<a id="type-mutual_constr_b"></a>
+
+###### and mutual_constr_b = 
+
+<a id="type-mutual_constr_b.B"></a>
+
+> | B
+
+<a id="type-mutual_constr_b.A_ish"></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).
+
+<a id="type-rec_obj"></a>
+
+###### type rec_obj =
+
+> < f : int ; g : unit -> unit ; h : [rec_obj](#type-rec_obj) >
+
+<a id="type-open_obj"></a>
+
+###### type 'a open_obj =
+
+> < f : int ; g : unit -> unit.. > as 'a
+
+<a id="type-oof"></a>
+
+###### type 'a oof =
+
+> < a : unit.. > as 'a -> 'a
+
+<a id="type-any_obj"></a>
+
+###### type 'a any_obj =
+
+> < .. > as 'a
+
+<a id="type-empty_obj"></a>
+
+###### type empty_obj =
+
+> <  >
+
+<a id="type-one_meth"></a>
+
+###### type one_meth =
+
+> < meth : unit >
+
+<a id="type-ext"></a>
+
+###### type ext =
+
+> ..
+
+A mystery wrapped in an ellipsis
+
+<a id="extension-decl-ExtA"></a>
+
+###### type [ext](#type-ext) += 
+
+<a id="extension-ExtA"></a>
+
+> | ExtA
+
+<a id="extension-decl-ExtB"></a>
+
+###### type [ext](#type-ext) += 
+
+<a id="extension-ExtB"></a>
+
+> | ExtB
+
+<a id="extension-decl-ExtC"></a>
+
+###### type [ext](#type-ext) += 
+
+<a id="extension-ExtC"></a>
+
+> | ExtC of unit
+
+<a id="extension-ExtD"></a>
+
+> | ExtD of [ext](#type-ext)
+
+<a id="extension-decl-ExtE"></a>
+
+###### type [ext](#type-ext) += 
+
+<a id="extension-ExtE"></a>
+
+> | ExtE
+
+<a id="extension-decl-ExtF"></a>
+
+###### type [ext](#type-ext) += 
+
+<a id="extension-ExtF"></a>
+
+> | ExtF
+
+<a id="type-poly_ext"></a>
+
+###### type 'a poly_ext =
+
+> ..
+
+'a poly_ext
+
+<a id="extension-decl-Foo"></a>
+
+###### type [poly_ext](#type-poly_ext) += 
+
+<a id="extension-Foo"></a>
+
+> | Foo of 'b
+
+<a id="extension-Bar"></a>
+
+> | Bar of 'b * 'b
+
+'b poly_ext
+
+<a id="extension-decl-Quux"></a>
+
+###### type [poly_ext](#type-poly_ext) += 
+
+<a id="extension-Quux"></a>
+
+> | Quux of 'c
+
+'c poly_ext
+
+<a id="module-ExtMod"></a>
+
+###### module [ExtMod](Ocamlary.ExtMod.md)
+
+<a id="extension-decl-ZzzTop0"></a>
+
+###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += 
+
+<a id="extension-ZzzTop0"></a>
+
+> | ZzzTop0
+
+It's got the rock
+
+<a id="extension-decl-ZzzTop"></a>
+
+###### type [ExtMod.t](Ocamlary.ExtMod.md#type-t) += 
+
+<a id="extension-ZzzTop"></a>
+
+> | ZzzTop of unit
+
+and it packs a unit.
+
+<a id="val-launch_missiles"></a>
+
+###### val launch_missiles :
+
+> unit -> unit
+
+Rotate keys on my mark...
+
+<a id="type-my_mod"></a>
+
+###### type my_mod =
+
+> (module [COLLECTION](Ocamlary.module-type-COLLECTION.md))
+
+A brown paper package tied up with string
+
+<a id="class-empty_class"></a>
+
+###### class [empty_class](Ocamlary.empty_class.md)
+
+<a id="class-one_method_class"></a>
+
+###### class [one_method_class](Ocamlary.one_method_class.md)
+
+<a id="class-two_method_class"></a>
+
+###### class [two_method_class](Ocamlary.two_method_class.md)
+
+<a id="class-param_class"></a>
+
+###### class 'a [param_class](Ocamlary.param_class.md)
+
+<a id="type-my_unit_object"></a>
+
+###### type my_unit_object =
+
+> unit [param_class](Ocamlary.param_class.md)
+
+<a id="type-my_unit_class"></a>
+
+###### type 'a my_unit_class =
+
+> unit param_class as 'a
+
+<a id="module-Dep1"></a>
+
+###### module [Dep1](Ocamlary.Dep1.md)
+
+<a id="module-Dep2"></a>
+
+###### module [Dep2](Ocamlary.Dep2.md)
+
+<a id="type-dep1"></a>
+
+###### type dep1 =
+
+> [Dep2(Dep1).B.c](Ocamlary.Dep1.module-type-S.c.md)
+
+<a id="module-Dep3"></a>
+
+###### module [Dep3](Ocamlary.Dep3.md)
+
+<a id="module-Dep4"></a>
+
+###### module [Dep4](Ocamlary.Dep4.md)
+
+<a id="module-Dep5"></a>
+
+###### module [Dep5](Ocamlary.Dep5.md)
+
+<a id="type-dep2"></a>
+
+###### type dep2 =
+
+> [Dep5(Dep4).Z.X.b](Ocamlary.Dep4.module-type-T.md#type-b)
+
+<a id="type-dep3"></a>
+
+###### type dep3 =
+
+> [Dep5(Dep4).Z.Y.a](Ocamlary.Dep3.md#type-a)
+
+<a id="module-Dep6"></a>
+
+###### module [Dep6](Ocamlary.Dep6.md)
+
+<a id="module-Dep7"></a>
+
+###### module [Dep7](Ocamlary.Dep7.md)
+
+<a id="type-dep4"></a>
+
+###### type dep4 =
+
+> [Dep7(Dep6).M.Y.d](Ocamlary.Dep6.module-type-T.Y.md#type-d)
+
+<a id="module-Dep8"></a>
+
+###### module [Dep8](Ocamlary.Dep8.md)
+
+<a id="module-Dep9"></a>
+
+###### module [Dep9](Ocamlary.Dep9.md)
+
+<a id="module-type-Dep10"></a>
+
+###### module type [Dep10](Ocamlary.module-type-Dep10.md)
+
+<a id="module-Dep11"></a>
+
+###### module [Dep11](Ocamlary.Dep11.md)
+
+<a id="module-Dep12"></a>
+
+###### module [Dep12](Ocamlary.Dep12.md)
+
+<a id="module-Dep13"></a>
+
+###### module [Dep13](Ocamlary.Dep13.md)
+
+<a id="type-dep5"></a>
+
+###### type dep5 =
+
+> [Dep13.c](Ocamlary.Dep13.c.md)
+
+<a id="module-type-With1"></a>
+
+###### module type [With1](Ocamlary.module-type-With1.md)
+
+<a id="module-With2"></a>
+
+###### module [With2](Ocamlary.With2.md)
+
+<a id="module-With3"></a>
+
+###### module [With3](Ocamlary.With3.md)
+
+<a id="type-with1"></a>
+
+###### type with1 =
+
+> [With3.N.t](Ocamlary.With3.N.md#type-t)
+
+<a id="module-With4"></a>
+
+###### module [With4](Ocamlary.With4.md)
+
+<a id="type-with2"></a>
+
+###### type with2 =
+
+> [With4.N.t](Ocamlary.With4.N.md#type-t)
+
+<a id="module-With5"></a>
+
+###### module [With5](Ocamlary.With5.md)
+
+<a id="module-With6"></a>
+
+###### module [With6](Ocamlary.With6.md)
+
+<a id="module-With7"></a>
+
+###### module [With7](Ocamlary.With7.md)
+
+<a id="module-type-With8"></a>
+
+###### module type [With8](Ocamlary.module-type-With8.md)
+
+<a id="module-With9"></a>
+
+###### module [With9](Ocamlary.With9.md)
+
+<a id="module-With10"></a>
+
+###### module [With10](Ocamlary.With10.md)
+
+<a id="module-type-With11"></a>
+
+###### module type [With11](Ocamlary.module-type-With11.md)
+
+<a id="module-type-NestedInclude1"></a>
+
+###### module type [NestedInclude1](Ocamlary.module-type-NestedInclude1.md)
+
+<a id="module-type-NestedInclude2"></a>
+
+###### module type [NestedInclude2](Ocamlary.module-type-NestedInclude2.md)
+
+<a id="type-nested_include"></a>
+
+###### type nested_include =
+
+> int
+
+<a id="module-DoubleInclude1"></a>
+
+###### module [DoubleInclude1](Ocamlary.DoubleInclude1.md)
+
+<a id="module-DoubleInclude3"></a>
+
+###### module [DoubleInclude3](Ocamlary.DoubleInclude3.md)
+
+<a id="type-double_include"></a>
+
+###### type double_include
+
+<a id="module-IncludeInclude1"></a>
+
+###### module [IncludeInclude1](Ocamlary.IncludeInclude1.md)
+
+<a id="module-type-IncludeInclude2"></a>
+
+###### module type [IncludeInclude2](Ocamlary.module-type-IncludeInclude2.md)
+
+<a id="module-IncludeInclude2_M"></a>
+
+###### module [IncludeInclude2_M](Ocamlary.IncludeInclude2_M.md)
+
+<a id="type-include_include"></a>
+
+###### 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
+
+<a id="module-CanonicalTest"></a>
+
+###### 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
+
+<a id="module-Aliases"></a>
+
+###### 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
+
+<a id="module-type-M"></a>
+
+###### module type [M](Ocamlary.module-type-M.md)
+
+<a id="module-M"></a>
+
+###### 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)
+  
+
+<a id="module-Only_a_module"></a>
+
+###### 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)
+  
+
+<a id="module-type-TypeExt"></a>
+
+###### module type [TypeExt](Ocamlary.module-type-TypeExt.md)
+
+<a id="type-new_t"></a>
+
+###### type new_t =
+
+> ..
+
+<a id="extension-decl-C"></a>
+
+###### type [new_t](#type-new_t) += 
+
+<a id="extension-C"></a>
+
+> | C
+
+<a id="module-type-TypeExtPruned"></a>
+
+###### 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
new file mode 100644
index 0000000000..abcc142eaa
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+A
+
+Q
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..888457b937
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+A
+
+Q
+
+InnerModuleA
+
+Module `Q.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.module-type-A.Q.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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-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..21bb568bc7
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-A.Q.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+A
+
+Q
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.module-type-A.Q.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..f32503e3c8
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-A.Q.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+A
+
+Q
+
+Module `A.Q`
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.module-type-A.Q.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.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-A.md b/test/generators/markdown/Ocamlary.module-type-A.md
new file mode 100644
index 0000000000..6f28e59f69
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-A.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+A
+
+Module type `Ocamlary.A`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="module-Q"></a>
+
+###### 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
new file mode 100644
index 0000000000..331ba88661
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+B
+
+Q
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..8ba3ae9960
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+B
+
+Q
+
+InnerModuleA
+
+Module `Q.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.module-type-B.Q.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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-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..9604560ffa
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-B.Q.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+B
+
+Q
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.module-type-B.Q.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..4cb1188255
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-B.Q.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+B
+
+Q
+
+Module `B.Q`
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.module-type-B.Q.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.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-B.md b/test/generators/markdown/Ocamlary.module-type-B.md
new file mode 100644
index 0000000000..4a6d27826f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-B.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+B
+
+Module type `Ocamlary.B`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="module-Q"></a>
+
+###### 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
new file mode 100644
index 0000000000..a6a61bf93a
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+C
+
+Q
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..7fb5375ddc
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+C
+
+Q
+
+InnerModuleA
+
+Module `Q.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.module-type-C.Q.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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-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..d4a28ea8a8
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-C.Q.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+C
+
+Q
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.module-type-C.Q.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..60b4fd80c7
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-C.Q.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+C
+
+Q
+
+Module `C.Q`
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.module-type-C.Q.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.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-C.md b/test/generators/markdown/Ocamlary.module-type-C.md
new file mode 100644
index 0000000000..6903212f21
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-C.md
@@ -0,0 +1,23 @@
+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
+  
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="module-Q"></a>
+
+###### 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..8f72879b93
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+COLLECTION
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..4cb1c304e0
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.md
@@ -0,0 +1,31 @@
+Ocamlary
+
+COLLECTION
+
+InnerModuleA
+
+Module `COLLECTION.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.module-type-COLLECTION.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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-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..14942cd3ca
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+COLLECTION
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.module-type-COLLECTION.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..89eb207813
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-COLLECTION.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+COLLECTION
+
+Module type `Ocamlary.COLLECTION`
+
+module type of
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.module-type-COLLECTION.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-COLLECTION.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+This comment is for `InnerModuleTypeA`.
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..11e184e1af
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-Dep10.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+Dep10
+
+Module type `Ocamlary.Dep10`
+
+<a id="type-t"></a>
+
+###### 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..eceadec323
--- /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
+
+<a id="type-t"></a>
+
+###### type t
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..5e31f3971e
--- /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
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..f45fbcf788
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-IncludeInclude2.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+IncludeInclude2
+
+Module type `Ocamlary.IncludeInclude2`
+
+<a id="type-include_include"></a>
+
+###### type include_include
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..70df33c53d
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-IncludeModuleType.md
@@ -0,0 +1,9 @@
+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..d763ff22d9
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-IncludedB.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+IncludedB
+
+Module type `Ocamlary.IncludedB`
+
+<a id="type-s"></a>
+
+###### type s
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..efdbfdff6d
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-M.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+M
+
+Module type `Ocamlary.M`
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..408bc59f69
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+MMM
+
+C
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..213099c295
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+MMM
+
+C
+
+InnerModuleA
+
+Module `C.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.module-type-MMM.C.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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-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..4b12bcaa97
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,21 @@
+Ocamlary
+
+MMM
+
+C
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.module-type-MMM.C.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..c0dd90010c
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-MMM.C.md
@@ -0,0 +1,33 @@
+Ocamlary
+
+MMM
+
+C
+
+Module `MMM.C`
+
+This comment is for `CollectionModule`.
+
+<a id="type-collection"></a>
+
+###### type collection
+
+This comment is for `collection`.
+
+<a id="type-element"></a>
+
+###### type element
+
+<a id="module-InnerModuleA"></a>
+
+###### module [InnerModuleA](Ocamlary.module-type-MMM.C.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.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-MMM.md b/test/generators/markdown/Ocamlary.module-type-MMM.md
new file mode 100644
index 0000000000..835d2dbf75
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-MMM.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+MMM
+
+Module type `Ocamlary.MMM`
+
+<a id="module-C"></a>
+
+###### 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
new file mode 100644
index 0000000000..ba4762a885
--- /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
+
+<a id="type-t"></a>
+
+###### type t
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..97726c9f67
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude1.md
@@ -0,0 +1,10 @@
+Ocamlary
+
+NestedInclude1
+
+Module type `Ocamlary.NestedInclude1`
+
+<a id="module-type-NestedInclude2"></a>
+
+###### 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
new file mode 100644
index 0000000000..310e4b1d7a
--- /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`
+
+<a id="type-nested_include"></a>
+
+###### type nested_include
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..f81609df90
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-NestedInclude2.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+NestedInclude2
+
+Module type `Ocamlary.NestedInclude2`
+
+<a id="type-nested_include"></a>
+
+###### type nested_include
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..987a93d37e
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-RECOLLECTION.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+RECOLLECTION
+
+Module type `Ocamlary.RECOLLECTION`
+
+<a id="module-C"></a>
+
+###### 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..4a3e052079
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+RecollectionModule
+
+InnerModuleA
+
+InnerModuleA'
+
+Module `InnerModuleA.InnerModuleA'`
+
+This comment is for `InnerModuleA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ( unit, unit ) [a_function](Ocamlary.md#type-a_function)
+
+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
new file mode 100644
index 0000000000..8b2ecda941
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.md
@@ -0,0 +1,31 @@
+Ocamlary
+
+RecollectionModule
+
+InnerModuleA
+
+Module `RecollectionModule.InnerModuleA`
+
+This comment is for `InnerModuleA`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [collection](Ocamlary.module-type-RecollectionModule.md#type-collection)
+
+This comment is for `t`.
+
+<a id="module-InnerModuleA'"></a>
+
+###### module
+[InnerModuleA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md)
+
+This comment is for `InnerModuleA'`.
+
+<a id="module-type-InnerModuleTypeA'"></a>
+
+###### 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.InnerModuleA.module-type-InnerModuleTypeA'.md b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md
new file mode 100644
index 0000000000..bf1a7d398b
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+RecollectionModule
+
+InnerModuleA
+
+InnerModuleTypeA'
+
+Module type `InnerModuleA.InnerModuleTypeA'`
+
+This comment is for `InnerModuleTypeA'`.
+
+<a id="type-t"></a>
+
+###### type t =
+
+> [InnerModuleA'.t](Ocamlary.module-type-RecollectionModule.InnerModuleA.InnerModuleA'.md#type-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
new file mode 100644
index 0000000000..c5ae6dad29
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-RecollectionModule.md
@@ -0,0 +1,32 @@
+Ocamlary
+
+RecollectionModule
+
+Module type `Ocamlary.RecollectionModule`
+
+<a id="type-collection"></a>
+
+###### type collection =
+
+> [CollectionModule.element](Ocamlary.CollectionModule.md#type-element) list
+
+<a id="type-element"></a>
+
+###### type element =
+
+> [CollectionModule.collection](Ocamlary.CollectionModule.md#type-collection)
+
+<a id="module-InnerModuleA"></a>
+
+###### module
+[InnerModuleA](Ocamlary.module-type-RecollectionModule.InnerModuleA.md)
+
+This comment is for `InnerModuleA`.
+
+<a id="module-type-InnerModuleTypeA"></a>
+
+###### module type InnerModuleTypeA =
+
+> [InnerModuleA.InnerModuleTypeA'](Ocamlary.module-type-RecollectionModule.InnerModuleA.module-type-InnerModuleTypeA'.md)
+
+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
new file mode 100644
index 0000000000..2aee21fad4
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-SigForMod.Inner.md
@@ -0,0 +1,12 @@
+Ocamlary
+
+SigForMod
+
+Inner
+
+Module `SigForMod.Inner`
+
+<a id="module-type-Empty"></a>
+
+###### 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
new file mode 100644
index 0000000000..48d1d571e1
--- /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`
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..c177a6d56f
--- /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.
+
+<a id="module-Inner"></a>
+
+###### 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
new file mode 100644
index 0000000000..cc52b8ba66
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.md
@@ -0,0 +1,29 @@
+Ocamlary
+
+SuperSig
+
+Module type `Ocamlary.SuperSig`
+
+<a id="module-type-SubSigA"></a>
+
+###### module type
+[SubSigA](Ocamlary.module-type-SuperSig.module-type-SubSigA.md)
+
+<a id="module-type-SubSigB"></a>
+
+###### module type
+[SubSigB](Ocamlary.module-type-SuperSig.module-type-SubSigB.md)
+
+<a id="module-type-EmptySig"></a>
+
+###### module type
+[EmptySig](Ocamlary.module-type-SuperSig.module-type-EmptySig.md)
+
+<a id="module-type-One"></a>
+
+###### module type [One](Ocamlary.module-type-SuperSig.module-type-One.md)
+
+<a id="module-type-SuperSig"></a>
+
+###### 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
new file mode 100644
index 0000000000..d2802b1fc3
--- /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`
+
+<a id="type-not_actually_empty"></a>
+
+###### 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
new file mode 100644
index 0000000000..b480de2f88
--- /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`
+
+<a id="type-two"></a>
+
+###### 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
new file mode 100644
index 0000000000..bcbd524f78
--- /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`
+
+<a id="type-sub_sig_a_mod"></a>
+
+###### 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
new file mode 100644
index 0000000000..5dd0dd483f
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigA.md
@@ -0,0 +1,18 @@
+Ocamlary
+
+SuperSig
+
+SubSigA
+
+Module type `SuperSig.SubSigA`
+
+### A Labeled Section Header Inside of a Signature
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="module-SubSigAMod"></a>
+
+###### 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
new file mode 100644
index 0000000000..b8a214b178
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-SuperSig.module-type-SubSigB.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+SuperSig
+
+SubSigB
+
+Module type `SuperSig.SubSigB`
+
+### Another Labeled Section Header Inside of a Signature
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..315d829ca3
--- /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`
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..560c308a0c
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.IncludedA.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+ToInclude
+
+IncludedA
+
+Module `ToInclude.IncludedA`
+
+<a id="type-t"></a>
+
+###### type t
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..f4e70e5a10
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-ToInclude.md
@@ -0,0 +1,14 @@
+Ocamlary
+
+ToInclude
+
+Module type `Ocamlary.ToInclude`
+
+<a id="module-IncludedA"></a>
+
+###### module [IncludedA](Ocamlary.module-type-ToInclude.IncludedA.md)
+
+<a id="module-type-IncludedB"></a>
+
+###### 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
new file mode 100644
index 0000000000..3a3a6d15ff
--- /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`
+
+<a id="type-s"></a>
+
+###### type s
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..f606b84c58
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-TypeExt.md
@@ -0,0 +1,25 @@
+Ocamlary
+
+TypeExt
+
+Module type `Ocamlary.TypeExt`
+
+<a id="type-t"></a>
+
+###### type t =
+
+> ..
+
+<a id="extension-decl-C"></a>
+
+###### type [t](#type-t) += 
+
+<a id="extension-C"></a>
+
+> | C
+
+<a id="val-f"></a>
+
+###### 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..f681175728
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-TypeExtPruned.md
@@ -0,0 +1,19 @@
+Ocamlary
+
+TypeExtPruned
+
+Module type `Ocamlary.TypeExtPruned`
+
+<a id="extension-decl-C"></a>
+
+###### type [new_t](Ocamlary.md#type-new_t) += 
+
+<a id="extension-C"></a>
+
+> | C
+
+<a id="val-f"></a>
+
+###### 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..2779578daf
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With1.M.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+With1
+
+M
+
+Module `With1.M`
+
+<a id="module-type-S"></a>
+
+###### module type S
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..e9c27d3bad
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With1.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+With1
+
+Module type `Ocamlary.With1`
+
+<a id="module-M"></a>
+
+###### module [M](Ocamlary.module-type-With1.M.md)
+
+<a id="module-N"></a>
+
+###### 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..56d197d763
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With11.N.md
@@ -0,0 +1,13 @@
+Ocamlary
+
+With11
+
+N
+
+Module `With11.N`
+
+<a id="type-t"></a>
+
+###### 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..e93896f7a9
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With11.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+With11
+
+Module type `Ocamlary.With11`
+
+<a id="module-M"></a>
+
+###### module M =
+
+> [With9](Ocamlary.With9.md)
+
+<a id="module-N"></a>
+
+###### module [N](Ocamlary.module-type-With11.N.md)
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..f324d9c3b0
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With8.M.N.md
@@ -0,0 +1,15 @@
+Ocamlary
+
+With8
+
+M
+
+N
+
+Module `M.N`
+
+<a id="type-t"></a>
+
+###### 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..2096674b6b
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With8.M.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+With8
+
+M
+
+Module `With8.M`
+
+<a id="module-type-S"></a>
+
+###### module type S =
+
+> [With5.S](Ocamlary.With5.module-type-S.md)
+
+<a id="module-N"></a>
+
+###### 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
new file mode 100644
index 0000000000..8d46410c6c
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.module-type-With8.md
@@ -0,0 +1,9 @@
+Ocamlary
+
+With8
+
+Module type `Ocamlary.With8`
+
+<a id="module-M"></a>
+
+###### module [M](Ocamlary.module-type-With8.M.md)
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..a398dd13bd
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.one_method_class.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+one_method_class
+
+Class `Ocamlary.one_method_class`
+
+<a id="method-go"></a>
+
+###### 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..2a6db27d60
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.param_class.md
@@ -0,0 +1,11 @@
+Ocamlary
+
+param_class
+
+Class `Ocamlary.param_class`
+
+<a id="method-v"></a>
+
+###### method v :
+
+> 'a
diff --git a/test/generators/markdown/Ocamlary.two_method_class.md b/test/generators/markdown/Ocamlary.two_method_class.md
new file mode 100644
index 0000000000..0757d89fe2
--- /dev/null
+++ b/test/generators/markdown/Ocamlary.two_method_class.md
@@ -0,0 +1,17 @@
+Ocamlary
+
+two_method_class
+
+Class `Ocamlary.two_method_class`
+
+<a id="method-one"></a>
+
+###### method one :
+
+> [one_method_class](Ocamlary.one_method_class.md)
+
+<a id="method-undo"></a>
+
+###### 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..96ac669330
--- /dev/null
+++ b/test/generators/markdown/Recent.X.md
@@ -0,0 +1,29 @@
+Recent
+
+X
+
+Module `Recent.X`
+
+<a id="module-L"></a>
+
+###### module L :=
+
+> [Z.Y](Recent.Z.Y.md)
+
+<a id="type-t"></a>
+
+###### type t =
+
+> int [Z.Y.X.t](Recent.Z.Y.X.md#type-t)
+
+<a id="type-u"></a>
+
+###### type u :=
+
+> int
+
+<a id="type-v"></a>
+
+###### 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..3d83ebbb46
--- /dev/null
+++ b/test/generators/markdown/Recent.Z.Y.X.md
@@ -0,0 +1,13 @@
+Recent
+
+Z
+
+Y
+
+X
+
+Module `Y.X`
+
+<a id="type-t"></a>
+
+###### type 'a t
diff --git a/test/generators/markdown/Recent.Z.Y.md b/test/generators/markdown/Recent.Z.Y.md
new file mode 100644
index 0000000000..b91a2781a6
--- /dev/null
+++ b/test/generators/markdown/Recent.Z.Y.md
@@ -0,0 +1,11 @@
+Recent
+
+Z
+
+Y
+
+Module `Z.Y`
+
+<a id="module-X"></a>
+
+###### module [X](Recent.Z.Y.X.md)
diff --git a/test/generators/markdown/Recent.Z.md b/test/generators/markdown/Recent.Z.md
new file mode 100644
index 0000000000..69d9579d66
--- /dev/null
+++ b/test/generators/markdown/Recent.Z.md
@@ -0,0 +1,9 @@
+Recent
+
+Z
+
+Module `Recent.Z`
+
+<a id="module-Y"></a>
+
+###### module [Y](Recent.Z.Y.md)
diff --git a/test/generators/markdown/Recent.md b/test/generators/markdown/Recent.md
new file mode 100644
index 0000000000..fc9087421a
--- /dev/null
+++ b/test/generators/markdown/Recent.md
@@ -0,0 +1,151 @@
+Recent
+
+Module `Recent`
+
+<a id="module-type-S"></a>
+
+###### module type [S](Recent.module-type-S.md)
+
+<a id="module-type-S1"></a>
+
+###### module type [S1](Recent.module-type-S1.md)
+
+<a id="type-variant"></a>
+
+###### type variant = 
+
+<a id="type-variant.A"></a>
+
+> | A
+
+<a id="type-variant.B"></a>
+
+> | B of int
+
+<a id="type-variant.C"></a>
+
+> | C
+
+foo
+
+<a id="type-variant.D"></a>
+
+> | D
+
+_bar_
+
+<a id="type-variant.E"></a>
+
+> | E of {
+
+<a id="type-variant.a"></a>
+
+> a : int;
+
+######    }
+
+<a id="type-gadt"></a>
+
+###### type _ gadt = 
+
+<a id="type-gadt.A"></a>
+
+> | A : int [gadt](#type-gadt)
+
+<a id="type-gadt.B"></a>
+
+> | B : int -> string [gadt](#type-gadt)
+
+foo
+
+<a id="type-gadt.C"></a>
+
+> | C : {
+
+<a id="type-gadt.a"></a>
+
+> a : int;
+
+######    }
+
+ -> unit [gadt](#type-gadt)
+
+<a id="type-polymorphic_variant"></a>
+
+###### type polymorphic_variant = [ 
+
+<a id="type-polymorphic_variant.A"></a>
+
+> | \`A
+
+<a id="type-polymorphic_variant.B"></a>
+
+> | \`B of int
+
+<a id="type-polymorphic_variant.C"></a>
+
+> | \`C
+
+foo
+
+<a id="type-polymorphic_variant.D"></a>
+
+> | \`D
+
+bar
+
+######  ]
+
+ ]
+
+<a id="type-empty_variant"></a>
+
+###### type empty_variant =
+
+> |
+
+<a id="type-nonrec_"></a>
+
+###### type nonrec nonrec_ =
+
+> int
+
+<a id="type-empty_conj"></a>
+
+###### type empty_conj = 
+
+<a id="type-empty_conj.X"></a>
+
+> | X : [< \`X of & 'a & int * float ] -> [empty_conj](#type-empty_conj)
+
+<a id="type-conj"></a>
+
+###### type conj = 
+
+<a id="type-conj.X"></a>
+
+> | X : [< \`X of int & [< \`B of int & float ] ] -> [conj](#type-conj)
+
+<a id="val-empty_conj"></a>
+
+###### val empty_conj :
+
+> [< \`X of & 'a & int * float ]
+
+<a id="val-conj"></a>
+
+###### val conj :
+
+> [< \`X of int & [< \`B of int & float ] ]
+
+<a id="module-Z"></a>
+
+###### module [Z](Recent.Z.md)
+
+<a id="module-X"></a>
+
+###### module [X](Recent.X.md)
+
+<a id="module-type-PolyS"></a>
+
+###### 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
new file mode 100644
index 0000000000..baf12a0bda
--- /dev/null
+++ b/test/generators/markdown/Recent.module-type-PolyS.md
@@ -0,0 +1,21 @@
+Recent
+
+PolyS
+
+Module type `Recent.PolyS`
+
+<a id="type-t"></a>
+
+###### type t = [ 
+
+<a id="type-t.A"></a>
+
+> | \`A
+
+<a id="type-t.B"></a>
+
+> | \`B
+
+######  ]
+
+ ]
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..72958f3ad1
--- /dev/null
+++ b/test/generators/markdown/Recent.module-type-S.md
@@ -0,0 +1,5 @@
+Recent
+
+S
+
+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
new file mode 100644
index 0000000000..dc92670e19
--- /dev/null
+++ b/test/generators/markdown/Recent.module-type-S1.argument-1-_.md
@@ -0,0 +1,7 @@
+Recent
+
+S1
+
+1-_
+
+Parameter `S1.1-_`
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..502dbaebce
--- /dev/null
+++ b/test/generators/markdown/Recent.module-type-S1.md
@@ -0,0 +1,13 @@
+Recent
+
+S1
+
+Module type `Recent.S1`
+
+# Parameters
+
+<a id="argument-1-_"></a>
+
+###### module [_](Recent.module-type-S1.argument-1-_.md)
+
+# Signature
diff --git a/test/generators/markdown/Recent_impl.B.md b/test/generators/markdown/Recent_impl.B.md
new file mode 100644
index 0000000000..d974f03450
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.B.md
@@ -0,0 +1,13 @@
+Recent_impl
+
+B
+
+Module `Recent_impl.B`
+
+<a id="type-t"></a>
+
+###### type t = 
+
+<a id="type-t.B"></a>
+
+> | B
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..b0ffff3fa9
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.Foo.A.md
@@ -0,0 +1,15 @@
+Recent_impl
+
+Foo
+
+A
+
+Module `Foo.A`
+
+<a id="type-t"></a>
+
+###### type t = 
+
+<a id="type-t.A"></a>
+
+> | A
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..eff358642e
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.Foo.B.md
@@ -0,0 +1,15 @@
+Recent_impl
+
+Foo
+
+B
+
+Module `Foo.B`
+
+<a id="type-t"></a>
+
+###### type t = 
+
+<a id="type-t.B"></a>
+
+> | B
diff --git a/test/generators/markdown/Recent_impl.Foo.md b/test/generators/markdown/Recent_impl.Foo.md
new file mode 100644
index 0000000000..d139f5aefe
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.Foo.md
@@ -0,0 +1,13 @@
+Recent_impl
+
+Foo
+
+Module `Recent_impl.Foo`
+
+<a id="module-A"></a>
+
+###### module [A](Recent_impl.Foo.A.md)
+
+<a id="module-B"></a>
+
+###### module [B](Recent_impl.Foo.B.md)
diff --git a/test/generators/markdown/Recent_impl.md b/test/generators/markdown/Recent_impl.md
new file mode 100644
index 0000000000..6e18d42fa6
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.md
@@ -0,0 +1,25 @@
+Recent_impl
+
+Module `Recent_impl`
+
+<a id="module-Foo"></a>
+
+###### module [Foo](Recent_impl.Foo.md)
+
+<a id="module-B"></a>
+
+###### module [B](Recent_impl.B.md)
+
+<a id="type-u"></a>
+
+###### type u
+
+<a id="module-type-S"></a>
+
+###### module type [S](Recent_impl.module-type-S.md)
+
+<a id="module-B'"></a>
+
+###### 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..1d33fdde97
--- /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-_`
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..db1a999ceb
--- /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
+
+<a id="argument-1-_"></a>
+
+###### module [_](Recent_impl.module-type-S.F.argument-1-_.md)
+
+# Signature
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..910d12c348
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.module-type-S.X.md
@@ -0,0 +1,7 @@
+Recent_impl
+
+S
+
+X
+
+Module `S.X`
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..33750a376d
--- /dev/null
+++ b/test/generators/markdown/Recent_impl.module-type-S.md
@@ -0,0 +1,19 @@
+Recent_impl
+
+S
+
+Module type `Recent_impl.S`
+
+<a id="module-F"></a>
+
+###### module [F](Recent_impl.module-type-S.F.md)
+
+<a id="module-X"></a>
+
+###### module [X](Recent_impl.module-type-S.X.md)
+
+<a id="val-f"></a>
+
+###### 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..10bcca8174
--- /dev/null
+++ b/test/generators/markdown/Section.md
@@ -0,0 +1,35 @@
+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
+
+<a id="val-foo"></a>
+
+###### val foo :
+
+> unit
+
+# Empty section
+
+# within a comment
+
+## and one with a nested section
+
+# _This_ `section` **title** <sub>has</sub> <sup>markup</sup>
+
+But links are impossible thanks to the parser, so we never have trouble
+rendering a section title in a table of contents – no link will be nested
+inside another link.
diff --git a/test/generators/markdown/Stop.N.md b/test/generators/markdown/Stop.N.md
new file mode 100644
index 0000000000..ae8899e250
--- /dev/null
+++ b/test/generators/markdown/Stop.N.md
@@ -0,0 +1,11 @@
+Stop
+
+N
+
+Module `Stop.N`
+
+<a id="val-quux"></a>
+
+###### val quux :
+
+> int
diff --git a/test/generators/markdown/Stop.md b/test/generators/markdown/Stop.md
new file mode 100644
index 0000000000..10df64d1f7
--- /dev/null
+++ b/test/generators/markdown/Stop.md
@@ -0,0 +1,35 @@
+Stop
+
+Module `Stop`
+
+This test cases exercises stop comments.
+
+<a id="val-foo"></a>
+
+###### 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.
+
+<a id="module-N"></a>
+
+###### module [N](Stop.N.md)
+
+<a id="val-lol"></a>
+
+###### 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..5efb036d5e
--- /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`
+
+<a id="type-t"></a>
+
+###### type t
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..6de5649fb2
--- /dev/null
+++ b/test/generators/markdown/Stop_dead_link_doc.md
@@ -0,0 +1,61 @@
+Stop_dead_link_doc
+
+Module `Stop_dead_link_doc`
+
+<a id="module-Foo"></a>
+
+###### module [Foo](Stop_dead_link_doc.Foo.md)
+
+<a id="type-foo"></a>
+
+###### type foo = 
+
+<a id="type-foo.Bar"></a>
+
+> | Bar of [Foo.t](Stop_dead_link_doc.Foo.md#type-t)
+
+<a id="type-bar"></a>
+
+###### type bar = 
+
+<a id="type-bar.Bar"></a>
+
+> | Bar of {
+
+<a id="type-bar.field"></a>
+
+> field : [Foo.t](Stop_dead_link_doc.Foo.md#type-t);
+
+######    }
+
+<a id="type-foo_"></a>
+
+###### type foo_ = 
+
+<a id="type-foo_.Bar_"></a>
+
+> | Bar_ of int * [Foo.t](Stop_dead_link_doc.Foo.md#type-t) * int
+
+<a id="type-bar_"></a>
+
+###### type bar_ = 
+
+<a id="type-bar_.Bar__"></a>
+
+> | Bar__ of [Foo.t](Stop_dead_link_doc.Foo.md#type-t) option
+
+<a id="type-another_foo"></a>
+
+###### type another_foo
+
+<a id="type-another_bar"></a>
+
+###### type another_bar
+
+<a id="type-another_foo_"></a>
+
+###### type another_foo_
+
+<a id="type-another_bar_"></a>
+
+###### type another_bar_
diff --git a/test/generators/markdown/Toplevel_comments.Alias.md b/test/generators/markdown/Toplevel_comments.Alias.md
new file mode 100644
index 0000000000..dafaaf7973
--- /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.
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..6e09566259
--- /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`
+
+<a id="type-t"></a>
+
+###### type t
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..6389c8bf65
--- /dev/null
+++ b/test/generators/markdown/Toplevel_comments.Comments_on_open.md
@@ -0,0 +1,14 @@
+Toplevel_comments
+
+Comments_on_open
+
+Module `Toplevel_comments.Comments_on_open`
+
+<a id="module-M"></a>
+
+###### 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
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..9c34bb0b4d
--- /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.
+
+<a id="type-t"></a>
+
+###### type t
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..28f67e8d93
--- /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.
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Toplevel_comments.M''.md b/test/generators/markdown/Toplevel_comments.M''.md
new file mode 100644
index 0000000000..f9d706a980
--- /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.
diff --git a/test/generators/markdown/Toplevel_comments.M'.md b/test/generators/markdown/Toplevel_comments.M'.md
new file mode 100644
index 0000000000..876cb421b6
--- /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
diff --git a/test/generators/markdown/Toplevel_comments.M.md b/test/generators/markdown/Toplevel_comments.M.md
new file mode 100644
index 0000000000..7de0e59083
--- /dev/null
+++ b/test/generators/markdown/Toplevel_comments.M.md
@@ -0,0 +1,7 @@
+Toplevel_comments
+
+M
+
+Module `Toplevel_comments.M`
+
+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
new file mode 100644
index 0000000000..40045252ec
--- /dev/null
+++ b/test/generators/markdown/Toplevel_comments.Ref_in_synopsis.md
@@ -0,0 +1,14 @@
+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.
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Toplevel_comments.c1.md b/test/generators/markdown/Toplevel_comments.c1.md
new file mode 100644
index 0000000000..915599be77
--- /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.
diff --git a/test/generators/markdown/Toplevel_comments.c2.md b/test/generators/markdown/Toplevel_comments.c2.md
new file mode 100644
index 0000000000..8eb1ba95ec
--- /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.
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..306fc65cb7
--- /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.
diff --git a/test/generators/markdown/Toplevel_comments.md b/test/generators/markdown/Toplevel_comments.md
new file mode 100644
index 0000000000..79e2bf24f0
--- /dev/null
+++ b/test/generators/markdown/Toplevel_comments.md
@@ -0,0 +1,90 @@
+Toplevel_comments
+
+Module `Toplevel_comments`
+
+A doc comment at the beginning of a module is considered to be that module's
+doc.
+
+<a id="module-type-T"></a>
+
+###### module type [T](Toplevel_comments.module-type-T.md)
+
+Doc of `T`, part 1.
+
+<a id="module-Include_inline"></a>
+
+###### module [Include_inline](Toplevel_comments.Include_inline.md)
+
+Doc of `T`, part 2.
+
+<a id="module-Include_inline'"></a>
+
+###### module [Include_inline'](Toplevel_comments.Include_inline'.md)
+
+Doc of `Include_inline`, part 1.
+
+<a id="module-type-Include_inline_T"></a>
+
+###### module type
+[Include_inline_T](Toplevel_comments.module-type-Include_inline_T.md)
+
+Doc of `T`, part 2.
+
+<a id="module-type-Include_inline_T'"></a>
+
+###### module type
+[Include_inline_T'](Toplevel_comments.module-type-Include_inline_T'.md)
+
+Doc of `Include_inline_T'`, part 1.
+
+<a id="module-M"></a>
+
+###### module [M](Toplevel_comments.M.md)
+
+Doc of `M`
+
+<a id="module-M'"></a>
+
+###### module [M'](Toplevel_comments.M'.md)
+
+Doc of `M'` from outside
+
+<a id="module-M''"></a>
+
+###### module [M''](Toplevel_comments.M''.md)
+
+Doc of `M''`, part 1.
+
+<a id="module-Alias"></a>
+
+###### module [Alias](Toplevel_comments.Alias.md)
+
+Doc of `Alias`.
+
+<a id="class-c1"></a>
+
+###### class [c1](Toplevel_comments.c1.md)
+
+Doc of `c1`, part 1.
+
+<a id="class-type-ct"></a>
+
+###### class type [ct](Toplevel_comments.class-type-ct.md)
+
+Doc of `ct`, part 1.
+
+<a id="class-c2"></a>
+
+###### class [c2](Toplevel_comments.c2.md)
+
+Doc of `c2`.
+
+<a id="module-Ref_in_synopsis"></a>
+
+###### module [Ref_in_synopsis](Toplevel_comments.Ref_in_synopsis.md)
+
+[`t`](Toplevel_comments.Ref_in_synopsis.md#type-t).
+
+<a id="module-Comments_on_open"></a>
+
+###### 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
new file mode 100644
index 0000000000..6e53b84362
--- /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.
+
+<a id="type-t"></a>
+
+###### 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
new file mode 100644
index 0000000000..fdd9c50c68
--- /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.
+
+<a id="type-t"></a>
+
+###### type t
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..d50c92b098
--- /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.
+
+<a id="type-t"></a>
+
+###### type t
diff --git a/test/generators/markdown/Type.md b/test/generators/markdown/Type.md
new file mode 100644
index 0000000000..6c8cdc41cf
--- /dev/null
+++ b/test/generators/markdown/Type.md
@@ -0,0 +1,447 @@
+Type
+
+Module `Type`
+
+<a id="type-abstract"></a>
+
+###### type abstract
+
+Some _documentation_.
+
+<a id="type-alias"></a>
+
+###### type alias =
+
+> int
+
+<a id="type-private_"></a>
+
+###### type private_ =
+
+> private int
+
+<a id="type-constructor"></a>
+
+###### type 'a constructor =
+
+> 'a
+
+<a id="type-arrow"></a>
+
+###### type arrow =
+
+> int -> int
+
+<a id="type-higher_order"></a>
+
+###### type higher_order =
+
+> ( int -> int ) -> int
+
+<a id="type-labeled"></a>
+
+###### type labeled =
+
+> l:int -> int
+
+<a id="type-optional"></a>
+
+###### type optional =
+
+> ?l:int -> int
+
+<a id="type-labeled_higher_order"></a>
+
+###### type labeled_higher_order =
+
+> ( l:int -> int ) -> ( ?l:int -> int ) -> int
+
+<a id="type-pair"></a>
+
+###### type pair =
+
+> int * int
+
+<a id="type-parens_dropped"></a>
+
+###### type parens_dropped =
+
+> int * int
+
+<a id="type-triple"></a>
+
+###### type triple =
+
+> int * int * int
+
+<a id="type-nested_pair"></a>
+
+###### type nested_pair =
+
+> (int * int) * int
+
+<a id="type-instance"></a>
+
+###### type instance =
+
+> int [constructor](#type-constructor)
+
+<a id="type-long"></a>
+
+###### 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
+
+<a id="type-variant_e"></a>
+
+###### type variant_e = {
+
+<a id="type-variant_e.a"></a>
+
+> a : int;
+
+###### }
+
+<a id="type-variant"></a>
+
+###### type variant = 
+
+<a id="type-variant.A"></a>
+
+> | A
+
+<a id="type-variant.B"></a>
+
+> | B of int
+
+<a id="type-variant.C"></a>
+
+> | C
+
+foo
+
+<a id="type-variant.D"></a>
+
+> | D
+
+_bar_
+
+<a id="type-variant.E"></a>
+
+> | E of [variant_e](#type-variant_e)
+
+<a id="type-variant_c"></a>
+
+###### type variant_c = {
+
+<a id="type-variant_c.a"></a>
+
+> a : int;
+
+###### }
+
+<a id="type-gadt"></a>
+
+###### type _ gadt = 
+
+<a id="type-gadt.A"></a>
+
+> | A : int [gadt](#type-gadt)
+
+<a id="type-gadt.B"></a>
+
+> | B : int -> string [gadt](#type-gadt)
+
+<a id="type-gadt.C"></a>
+
+> | C : [variant_c](#type-variant_c) -> unit [gadt](#type-gadt)
+
+<a id="type-degenerate_gadt"></a>
+
+###### type degenerate_gadt = 
+
+<a id="type-degenerate_gadt.A"></a>
+
+> | A : [degenerate_gadt](#type-degenerate_gadt)
+
+<a id="type-private_variant"></a>
+
+###### type private_variant = private 
+
+<a id="type-private_variant.A"></a>
+
+> | A
+
+<a id="type-record"></a>
+
+###### type record = {
+
+<a id="type-record.a"></a>
+
+> a : int;
+
+<a id="type-record.b"></a>
+
+> mutable b : int;
+
+<a id="type-record.c"></a>
+
+> c : int;
+
+foo
+
+<a id="type-record.d"></a>
+
+> d : int;
+
+_bar_
+
+<a id="type-record.e"></a>
+
+> e : 'a. 'a;
+
+###### }
+
+<a id="type-polymorphic_variant"></a>
+
+###### type polymorphic_variant = [ 
+
+<a id="type-polymorphic_variant.A"></a>
+
+> | \`A
+
+<a id="type-polymorphic_variant.B"></a>
+
+> | \`B of int
+
+<a id="type-polymorphic_variant.C"></a>
+
+> | \`C of int * unit
+
+<a id="type-polymorphic_variant.D"></a>
+
+> | \`D
+
+######  ]
+
+ ]
+
+<a id="type-polymorphic_variant_extension"></a>
+
+###### type polymorphic_variant_extension = [ 
+
+<a id="type-polymorphic_variant_extension.polymorphic_variant"></a>
+
+> | [polymorphic_variant](#type-polymorphic_variant)
+
+<a id="type-polymorphic_variant_extension.E"></a>
+
+> | \`E
+
+######  ]
+
+ ]
+
+<a id="type-nested_polymorphic_variant"></a>
+
+###### type nested_polymorphic_variant = [ 
+
+<a id="type-nested_polymorphic_variant.A"></a>
+
+> | \`A of [ \`B | \`C ]
+
+######  ]
+
+ ]
+
+<a id="type-private_extenion#row"></a>
+
+###### type private_extenion#row
+
+<a id="type-private_extenion"></a>
+
+###### and private_extenion = private [> 
+
+<a id="type-private_extenion.polymorphic_variant"></a>
+
+> | [polymorphic_variant](#type-polymorphic_variant)
+
+######  ]
+
+ ]
+
+<a id="type-object_"></a>
+
+###### type object_ =
+
+> < a : int ; b : int ; c : int >
+
+<a id="module-type-X"></a>
+
+###### module type [X](Type.module-type-X.md)
+
+<a id="type-module_"></a>
+
+###### type module_ =
+
+> (module [X](Type.module-type-X.md))
+
+<a id="type-module_substitution"></a>
+
+###### 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)
+
+<a id="type-covariant"></a>
+
+###### type +'a covariant
+
+<a id="type-contravariant"></a>
+
+###### type -'a contravariant
+
+<a id="type-bivariant"></a>
+
+###### type _ bivariant =
+
+> int
+
+<a id="type-binary"></a>
+
+###### type ('a, 'b) binary
+
+<a id="type-using_binary"></a>
+
+###### type using_binary =
+
+> ( int, int ) [binary](#type-binary)
+
+<a id="type-name"></a>
+
+###### type 'custom name
+
+<a id="type-constrained"></a>
+
+###### type 'a constrained =
+
+> 'a constraint 'a = int
+
+<a id="type-exact_variant"></a>
+
+###### type 'a exact_variant =
+
+> 'a constraint 'a = [ \`A | \`B of int ]
+
+<a id="type-lower_variant"></a>
+
+###### type 'a lower_variant =
+
+> 'a constraint 'a = [> \`A | \`B of int ]
+
+<a id="type-any_variant"></a>
+
+###### type 'a any_variant =
+
+> 'a constraint 'a = [>  ]
+
+<a id="type-upper_variant"></a>
+
+###### type 'a upper_variant =
+
+> 'a constraint 'a = [< \`A | \`B of int ]
+
+<a id="type-named_variant"></a>
+
+###### type 'a named_variant =
+
+> 'a constraint 'a = [< [polymorphic_variant](#type-polymorphic_variant) ]
+
+<a id="type-exact_object"></a>
+
+###### type 'a exact_object =
+
+> 'a constraint 'a = < a : int ; b : int >
+
+<a id="type-lower_object"></a>
+
+###### type 'a lower_object =
+
+> 'a constraint 'a = < a : int ; b : int.. >
+
+<a id="type-poly_object"></a>
+
+###### type 'a poly_object =
+
+> 'a constraint 'a = < a : 'a. 'a >
+
+<a id="type-double_constrained"></a>
+
+###### type ('a, 'b) double_constrained =
+
+> 'a * 'b constraint 'a = int constraint 'b = unit
+
+<a id="type-as_"></a>
+
+###### type as_ =
+
+> int as 'a * 'a
+
+<a id="type-extensible"></a>
+
+###### type extensible =
+
+> ..
+
+<a id="extension-decl-Extension"></a>
+
+###### type [extensible](#type-extensible) += 
+
+<a id="extension-Extension"></a>
+
+> | Extension
+
+Documentation for [`Extension`](#extension-Extension).
+
+<a id="extension-Another_extension"></a>
+
+> | Another_extension
+
+Documentation for [`Another_extension`](#extension-Another_extension).
+
+<a id="type-mutually"></a>
+
+###### type mutually = 
+
+<a id="type-mutually.A"></a>
+
+> | A of [recursive](#type-recursive)
+
+<a id="type-recursive"></a>
+
+###### and recursive = 
+
+<a id="type-recursive.B"></a>
+
+> | B of [mutually](#type-mutually)
+
+<a id="exception-Foo"></a>
+
+###### 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
new file mode 100644
index 0000000000..2ba8d30a45
--- /dev/null
+++ b/test/generators/markdown/Type.module-type-X.md
@@ -0,0 +1,13 @@
+Type
+
+X
+
+Module type `Type.X`
+
+<a id="type-t"></a>
+
+###### type t
+
+<a id="type-u"></a>
+
+###### type u
diff --git a/test/generators/markdown/Val.md b/test/generators/markdown/Val.md
new file mode 100644
index 0000000000..9690ef2106
--- /dev/null
+++ b/test/generators/markdown/Val.md
@@ -0,0 +1,25 @@
+Val
+
+Module `Val`
+
+<a id="val-documented"></a>
+
+###### val documented :
+
+> unit
+
+Foo.
+
+<a id="val-undocumented"></a>
+
+###### val undocumented :
+
+> unit
+
+<a id="val-documented_above"></a>
+
+###### val documented_above :
+
+> unit
+
+Bar.
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..a99de7ddc8
--- /dev/null
+++ b/test/generators/markdown/mld.md
@@ -0,0 +1,36 @@
+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.
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