diff --git a/CHANGES.md b/CHANGES.md
index 503669ea70..f7ae398ff7 100644
--- a/CHANGES.md
+++ b/CHANGES.md
@@ -3,6 +3,7 @@ UNRELEASED
 
 Additions
 - Source code rendering (@Julow, @panglesd, #909)
+- Handle tables markup (@panglesd, @gpetiot, #893)
 
 Bugfixes
 - Fix `--hidden` not always taken into account (@panglesd, #940)
diff --git a/doc/ocamldoc_differences.mld b/doc/ocamldoc_differences.mld
index 24e77545b4..b32bc6d23f 100644
--- a/doc/ocamldoc_differences.mld
+++ b/doc/ocamldoc_differences.mld
@@ -13,7 +13,7 @@ can be seen rendered by [odoc] {{!Odoc_examples.Markup.Foo}here}.
 The following describes the changes between what [odoc] understands and what’s in the OCaml manual.
 
 - Heading levels are more restrictive. In the manual, it suggests any whole number is acceptable. In [odoc],
-  we follow the HTML spec in allowing headings from 1-6, and we also allow heading level [0] for the title
+  similarly to the HTML spec, we allow headings from 1-5, and heading level [0] for the title
   of [.mld] files. [odoc] emits a warning for heading levels outside this range and caps them.
 
 {3 Omissions}
@@ -29,6 +29,7 @@ The following describes the changes between what [odoc] understands and what’s
   An other difference is that documentation starting with a heading or something that is not a paragraph won't have a synopsis ({{:https://github.com/ocaml/odoc/pull/643}github issue}).
 
 {3 Improvements}
+- [odoc] supports writing mathematics and tables with a specific syntax.
 - [odoc] has a better mechanism for disambiguating references in comments. See 'reference syntax' later in this document.
 - Built-in support for standalone [.mld] files. These are documents using the OCamldoc markup, but they’re rendered as distinct pages.
 - Structured output: [odoc] can produce output in a structured directory tree rather a set of files.
diff --git a/doc/odoc_for_authors.mld b/doc/odoc_for_authors.mld
index db9b963374..8a74fa2e7b 100644
--- a/doc/odoc_for_authors.mld
+++ b/doc/odoc_for_authors.mld
@@ -542,6 +542,74 @@ in block form this becomes:
 See the {{:https://katex.org/docs/supported.html}KaTeX documentation} for the
 HTML mode LaTeX support status.
 
+{2 Tables}
+
+Odoc 2.3 introduced new markup for tables. This markup comes in two flavors: the light syntax, and the heavy syntax.
+
+The heavy syntax uses several markup: [{table ...}] to define a table, [{tr ...}] to define a row, and [{th ...}] and [{td ...}] to respectively define a header cell and a data cell.
+Direct children of tables have to be rows, and direct children of rows have to be cells. Similarly, rows have to be direct children of tables, and cells direct children of row. Cells can contain any markup.
+
+For instance, the following table:
+
+{[
+  {table
+    {tr
+      {th Header 1}
+      {th Header 2}
+      {th Header 3}
+    }
+    {tr
+      {td Cell 1}
+      {td Cell with {e emphasized content}}
+      {td {v a block v} }
+    }
+  }
+]}
+
+would render as
+
+{table
+  {tr
+    {th Header 1}
+    {th Header 2}
+    {th Header 3}
+  }
+  {tr
+    {td Cell 1}
+    {td Cell with {e emphasized content}}
+    {td {v a block v} }
+  }
+}
+
+
+The light syntax has the advantages of being simple to read, even as plain text. It is very similar to the {{:https://github.github.com/gfm/#tables-extension-}GFM Markdown syntax}, with the exception that it has to be enclosed in [{t ...}], and that the inline markup is the ocamldoc one. It supports alignment for columns using the [:] notation, from the GFM syntax: [---] is the default alignment, [:--] left-aligned, [--:] right-aligned and [:---:] is centered.
+
+The following table, in light syntax:
+
+{[
+{t
+  | Header 1 | Header 2 | Header 3 | Header 4|
+  | :------: | --------:|:---------|---------|
+  | centered | right    | left     | default |
+    omitted  | bar at   | start and| finish
+  | {e emph} | and | unaligned | bars |
+}
+]}
+
+would render as
+
+{t
+  | Header 1 | Header 2 | Header 3 | Header 4|
+  | :------: | --------:|:---------|---------|
+  | centered | right    | left     | default |
+    omitted  | bar at   | start and| finish
+  | {e emph} | and | unaligned | bars |
+}
+
+The light syntax has the advantages of being arguably more readable for small tables, when viewing the source file directly. However, its content is restricted (for instance, no new line is allowed).
+The heavy syntax is easier to write, can be more readable for big tables, and supports having any kind of content inside. It does not support alignment (yet).
+
+
 {2 Stop Comments}
 
 The special comment:
diff --git a/odoc.opam b/odoc.opam
index 48bb6e4234..eee5a39239 100644
--- a/odoc.opam
+++ b/odoc.opam
@@ -24,6 +24,10 @@ Odoc is a documentation generator for OCaml. It reads doc comments,
 delimited with `(** ... *)`, and outputs HTML. 
 """
 
+pin-depends: [
+  ["odoc-parser.dev" "git+https://github.com/ocaml-doc/odoc-parser.git#f98cfe3"]
+]
+
 depends: [
   "odoc-parser" {>= "2.0.0"}
   "astring"
diff --git a/src/document/comment.ml b/src/document/comment.ml
index be0ff78d28..b4fb9698d5 100644
--- a/src/document/comment.ml
+++ b/src/document/comment.ml
@@ -258,6 +258,39 @@ let rec nestable_block_element : Comment.nestable_block_element -> Block.one =
       in
       let items = List.map f items in
       block @@ Block.List (kind, items)
+  | `Table { data; align } ->
+      let data =
+        List.map
+          (List.map (fun (cell, cell_type) ->
+               (nestable_block_element_list cell, cell_type)))
+          data
+      in
+      let generate_align data =
+        let max (a : int) b = if a < b then b else a in
+        (* Length of the longest line of the table *)
+        let max_length =
+          List.fold_left (fun m l -> max m (List.length l)) 0 data
+        in
+        let rec list_init i =
+          if i <= 0 then [] else Table.Default :: list_init (i - 1)
+        in
+        list_init max_length
+      in
+      let align =
+        match align with
+        | None -> generate_align data
+        | Some align ->
+            List.map
+              (function
+                | None -> Table.Default
+                | Some `Right -> Right
+                | Some `Left -> Left
+                | Some `Center -> Center)
+              align
+        (* We should also check wellness of number of table cells vs alignment,
+           and raise warnings *)
+      in
+      block @@ Table { data; align }
 
 and paragraph : Comment.paragraph -> Block.one = function
   | [ { value = `Raw_markup (target, s); _ } ] ->
diff --git a/src/document/doctree.ml b/src/document/doctree.ml
index 058d7d7ded..cc95eed9f8 100644
--- a/src/document/doctree.ml
+++ b/src/document/doctree.ml
@@ -384,6 +384,8 @@ end = struct
       | Inline x -> inline x
       | Paragraph x -> inline x
       | List (_, x) -> List.exists block x
+      | Table { data; align = _ } ->
+          List.exists (List.exists (fun (cell, _) -> block cell)) data
       | Description x -> description x
       | Math _ -> true
       | Source _ | Verbatim _ | Raw_markup _ -> false
diff --git a/src/document/types.ml b/src/document/types.ml
index 0ae2588098..a40c78b087 100644
--- a/src/document/types.ml
+++ b/src/document/types.ml
@@ -89,11 +89,22 @@ and Block : sig
     | Math of Math.t
     | Verbatim of string
     | Raw_markup of Raw_markup.t
+    | Table of t Table.t
 
   and list_type = Ordered | Unordered
 end =
   Block
 
+and Table : sig
+  type alignment = Left | Center | Right | Default
+
+  type 'a t = {
+    data : ('a * [ `Header | `Data ]) list list;
+    align : alignment list;
+  }
+end =
+  Table
+
 and DocumentedSrc : sig
   type 'a documented = {
     attrs : Class.t;
diff --git a/src/html/generator.ml b/src/html/generator.ml
index 9e89a071c4..215bb22cd2 100644
--- a/src/html/generator.ml
+++ b/src/html/generator.ml
@@ -177,6 +177,14 @@ let heading ~config ~resolve (h : Heading.t) =
   in
   mk ~a (anchor @ content @ source_link)
 
+let text_align = function
+  | Table.Left -> [ Html.a_style "text-align:left" ]
+  | Center -> [ Html.a_style "text-align:center" ]
+  | Right -> [ Html.a_style "text-align:right" ]
+  | Default -> []
+
+let cell_kind = function `Header -> Html.th | `Data -> Html.td
+
 let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
   let as_flow x = (x : phrasing Html.elt list :> flow Html.elt list) in
   let one (t : Block.one) =
@@ -192,6 +200,10 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
     | List (typ, l) ->
         let mk = match typ with Ordered -> Html.ol | Unordered -> Html.ul in
         mk_block mk (List.map (fun x -> Html.li (block ~config ~resolve x)) l)
+    | Table t ->
+        mk_block ~extra_class:[ "odoc-table" ]
+          (fun ?a x -> Html.table ?a x)
+          (mk_rows ~config ~resolve t)
     | Description l ->
         let item i =
           let a = class_ i.Description.attr in
@@ -213,6 +225,29 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
   in
   Utils.list_concat_map l ~f:one
 
+and mk_rows ~config ~resolve { align; data } =
+  let mk_row row =
+    let mk_cell ~align (x, h) =
+      let a = text_align align in
+      cell_kind ~a h (block ~config ~resolve x)
+    in
+    let alignment align =
+      match align with align :: q -> (align, q) | [] -> (Table.Default, [])
+      (* Second case is for recovering from a too short alignment list. A
+         warning should have been raised when loading the doc-comment. *)
+    in
+    let acc, _align =
+      List.fold_left
+        (fun (acc, aligns) (x, h) ->
+          let align, aligns = alignment aligns in
+          let cell = mk_cell ~align (x, h) in
+          (cell :: acc, aligns))
+        ([], align) row
+    in
+    Html.tr (List.rev acc)
+  in
+  List.map mk_row data
+
 (* This coercion is actually sound, but is not currently accepted by Tyxml.
    See https://github.com/ocsigen/tyxml/pull/265 for details
    Can be replaced by a simple type coercion once this is fixed
diff --git a/src/html_support_files/odoc.css b/src/html_support_files/odoc.css
index 0e4e5c9e8d..3826f7150b 100644
--- a/src/html_support_files/odoc.css
+++ b/src/html_support_files/odoc.css
@@ -701,6 +701,22 @@ td.def-doc *:first-child {
   padding-left: 12px;
 }
 
+/* Tables */
+
+.odoc-table {
+  margin: 1em;
+}
+
+.odoc-table td, .odoc-table th {
+  padding-left: 0.5em;
+  padding-right: 0.5em;
+  border: 1px solid black;
+}
+
+.odoc-table th {
+  font-weight: bold;
+}
+
 /* Mobile adjustements. */
 
 @media only screen and (max-width: 110ex) {
diff --git a/src/html_support_files/odoc_html_support_files.ml b/src/html_support_files/odoc_html_support_files.ml
index cafa82fcd4..de7b770a2f 100644
--- a/src/html_support_files/odoc_html_support_files.ml
+++ b/src/html_support_files/odoc_html_support_files.ml
@@ -76,12 +76,12 @@ module Internal = struct
 
   let d_37935d98135b118d937e895f4bb55add = "ack\",!0),ie(oe,le,ge,\"(\",\"\\\\lparen\",!0),ie(oe,le,ue,\")\",\"\\\\rparen\",!0),ie(se,le,xe,\"<\",\"\\\\textless\",!0),ie(se,le,xe,\">\",\"\\\\textgreater\",!0),ie(oe,le,ge,\"\\u230a\",\"\\\\lfloor\",!0),ie(oe,le,ue,\"\\u230b\",\"\\\\rfloor\",!0),ie(oe,le,ge,\"\\u2308\",\"\\\\lceil\",!0),ie(oe,le,ue,\"\\u2309\",\"\\\\rceil\",!0),ie(oe,le,xe,\"\\\\\",\"\\\\backslash\"),ie(oe,le,xe,\"\\u2223\",\"|\"),ie(oe,le,xe,\"\\u2223\",\"\\\\vert\"),ie(se,le,xe,\"|\",\"\\\\textbar\",!0),ie(oe,le,xe,\"\\u2225\",\"\\\\|\"),ie(oe,le,xe,\"\\u2225\",\"\\\\Vert\"),ie(se,le,xe,\"\\u2225\",\"\\\\textbardbl\"),ie(se,le,xe,\"~\",\"\\\\textasciitilde\"),ie(se,le,xe,\"\\\\\",\"\\\\textbackslash\"),ie(se,le,xe,\"^\",\"\\\\textasciicircum\"),ie(oe,le,be,\"\\u2191\",\"\\\\uparrow\",!0),ie(oe,le,be,\"\\u21d1\",\"\\\\Uparrow\",!0),ie(oe,le,be,\"\\u2193\",\"\\\\downarrow\",!0),ie(oe,le,be,\"\\u21d3\",\"\\\\Downarrow\",!0),ie(oe,le,be,\"\\u2195\",\"\\\\updownarrow\",!0),ie(oe,le,be,\"\\u21d5\",\"\\\\Updownarrow\",!0),ie(oe,le,fe,\"\\u2210\",\"\\\\coprod\"),ie(oe,le,fe,\"\\u22c1\",\"\\\\bigvee\"),ie(oe,le,fe,\"\\u22c0\",\"\\\\bigwedge\"),ie(oe,le,fe,\"\\u2a04\",\"\\\\biguplus\"),ie(oe,le,fe,\"\\u22c2\",\"\\\\bigcap\"),ie(oe,le,fe,\"\\u22c3\",\"\\\\bigcup\"),ie(oe,le,fe,\"\\u222b\",\"\\\\int\"),ie(oe,le,fe,\"\\u222b\",\"\\\\intop\"),ie(oe,le,fe,\"\\u222c\",\"\\\\iint\"),ie(oe,le,fe,\"\\u222d\",\"\\\\iiint\"),ie(oe,le,fe,\"\\u220f\",\"\\\\prod\"),ie(oe,le,fe,\"\\u2211\",\"\\\\sum\"),ie(oe,le,fe,\"\\u2a02\",\"\\\\bigotimes\"),ie(oe,le,fe,\"\\u2a01\",\"\\\\bigoplus\"),ie(oe,le,fe,\"\\u2a00\",\"\\\\bigodot\"),ie(oe,le,fe,\"\\u222e\",\"\\\\oint\"),ie(oe,le,fe,\"\\u222f\",\"\\\\oiint\"),ie(oe,le,fe,\"\\u2230\",\"\\\\oiiint\"),ie(oe,le,fe,\"\\u2a06\",\"\\\\bigsqcup\"),ie(oe,le,fe,\"\\u222b\",\"\\\\smallint\"),ie(se,le,pe,\"\\u2026\",\"\\\\textellipsis\"),ie(oe,le,pe,\"\\u2026\",\"\\\\mathellipsis\"),ie(se,le,pe,\"\\u2026\",\"\\\\ldots\",!0),ie(oe,le,pe,\"\\u2026\",\"\\\\ldots\",!0),ie(oe,le,pe,\"\\u22ef\",\"\\\\@cdots\",!0),ie(oe,le,pe,\"\\u22f1\",\"\\\\ddots\",!0),ie(oe,le,xe,\"\\u22ee\",\"\\\\varvdots\"),ie(oe,le,me,\"\\u02ca\",\"\\\\acute\"),ie(oe,le,me,\"\\u02cb\",\"\\\\grave\"),ie(oe,le,me,\"\\xa8\",\"\\\\ddot\"),ie(oe,le,me,\"~\",\"\\\\tilde\"),ie(oe,le,me,\"\\u02c9\",\"\\\\bar\"),ie(oe,le,me,\"\\u02d8\",\"\\\\breve\"),ie(oe,le,me,\"\\u02c7\",\"\\\\check\"),ie(oe,le,me,\"^\",\"\\\\hat\"),ie(oe,le,me,\"\\u20d7\",\"\\\\vec\"),ie(oe,le,me,\"\\u02d9\",\"\\\\dot\"),ie(oe,le,me,\"\\u02da\",\"\\\\mathring\"),ie(oe,le,de,\"\\ue131\",\"\\\\@imath\"),ie(oe,le,de,\"\\ue237\",\"\\\\@jmath\"),ie(oe,le,xe,\"\\u0131\",\"\\u0131\"),ie(oe,le,xe,\"\\u0237\",\"\\u0237\"),ie(se,le,xe,\"\\u0131\",\"\\\\i\",!0),ie(se,le,xe,\"\\u0237\",\"\\\\j\",!0),ie(se,le,xe,\"\\xdf\",\"\\\\ss\",!0),ie(se,le,xe,\"\\xe6\",\"\\\\ae\",!0),ie(se,le,xe,\"\\u0153\",\"\\\\oe\",!0),ie(se,le,xe,\"\\xf8\",\"\\\\o\",!0),ie(se,le,xe,\"\\xc6\",\"\\\\AE\",!0),ie(se,le,xe,\"\\u0152\",\"\\\\OE\",!0),ie(se,le,xe,\"\\xd8\",\"\\\\O\",!0),ie(se,le,me,\"\\u02ca\",\"\\\\'\"),ie(se,le,me,\"\\u02cb\",\"\\\\`\"),ie(se,le,me,\"\\u02c6\",\"\\\\^\"),ie(se,le,me,\"\\u02dc\",\"\\\\~\"),ie(se,le,me,\"\\u02c9\",\"\\\\=\"),ie(se,le,me,\"\\u02d8\",\"\\\\u\"),ie(se,le,me,\"\\u02d9\",\"\\\\.\"),ie(se,le,me,\"\\xb8\",\"\\\\c\"),ie(se,le,me,\"\\u02da\",\"\\\\r\"),ie(se,le,me,\"\\u02c7\",\"\\\\v\"),ie(se,le,me,\"\\xa8\",'\\\\\"'),ie(se,le,me,\"\\u02dd\",\"\\\\H\"),ie(se,le,me,\"\\u25ef\",\"\\\\textcircled\");var we={\"--\":!0,\"---\":!0,\"``\":!0,\"''\":!0};ie(se,le,xe,\"\\u2013\",\"--\",!0),ie(se,le,xe,\"\\u2013\",\"\\\\textendash\"),ie(se,le,xe,\"\\u2014\",\"---\",!0),ie(se,le,xe,\"\\u2014\",\"\\\\textemdash\"),ie(se,le,xe,\"\\u2018\",\"`\",!0),ie(se,le,xe,\"\\u2018\",\"\\\\textquoteleft\"),ie(se,le,xe,\"\\u2019\",\"'\",!0),ie(se,le,xe,\"\\u2019\",\"\\\\textquoteright\"),ie(se,le,xe,\"\\u201c\",\"``\",!0),ie(se,le,xe,\"\\u201c\",\"\\\\textquotedblleft\"),ie(se,le,xe,\"\\u201d\",\"''\",!0),ie(se,le,xe,\"\\u201d\",\"\\\\textquotedblright\"),ie(oe,le,xe,\"\\xb0\",\"\\\\degree\",!0),ie(se,le,xe,\"\\xb0\",\"\\\\degree\"),ie(se,le,xe,\"\\xb0\",\"\\\\textdegree\",!0),ie(oe,le,xe,\"\\xa3\",\"\\\\pounds\"),ie(oe,le,xe,\"\\xa3\",\"\\\\mathsterling\",!0),ie(se,le,xe,\"\\xa3\",\"\\\\pounds\"),ie(se,le,xe,\"\\xa3\",\"\\\\textsterling\",!0),ie(oe,he,xe,\"\\u2720\",\"\\\\maltese\"),ie(se,he,xe,\"\\u2720\",\"\\\\maltese\");for(var ke='0123456789/@.\"',Se=0;Se<ke.length;Se++){var Me=ke.charAt(Se);ie(oe,le,xe,Me,Me)}for(var ze='0123456789!@*()-=+\";:?/.,',Ae=0;Ae<ze.length;Ae++){var Te=ze.charAt(Ae);ie(se,le,xe,Te,Te)}for(var Be=\"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz\",Ce=0;Ce<Be.length;Ce++){var qe=Be.charAt(Ce);ie(oe,le,de,qe,qe),ie(se,le,xe,qe,qe)}ie(oe,he,xe,\"C\",\"\\u2102\"),ie(se,he,xe,\"C\",\"\\u2102\"),ie(oe,he,xe,\"H\",\"\\u210d\"),ie(se,he,xe,\"H\",\"\\u210d\"),ie(oe,he,xe"
 
-  let d_396665eb256e05372074b6eef49926af = "lay: block;\n}\n\n/* Sidebar and TOC */\n\n.odoc-toc:before {\n  display: block;\n  content: \"Contents\";\n  text-transform: uppercase;\n  font-size: 1em;\n  margin: 1.414em 0 0.5em;\n  font-weight: 500;\n  color: var(--toc-before-color);\n  line-height: 1.2;\n}\n\n.odoc-toc {\n  position: fixed;\n  top: 0px;\n  bottom: 0px;\n  left: 0px;\n  max-width: 30ex;\n  min-width: 26ex;\n  width: 20%;\n  background: var(--toc-background);\n  overflow: auto;\n  color: var(--toc-color);\n  padding-left: 2ex;\n  padding-right: 2ex;\n}\n\n.odoc-toc ul li a {\n  font-family: \"Fira Sans\", sans-serif;\n  font-size: 0.95em;\n  color: var(--color);\n  font-weight: 400;\n  line-height: 1.6em;\n  display: block;\n}\n\n.odoc-toc ul li a:hover {\n  box-shadow: none;\n  text-decoration: underline;\n}\n\n/* First level titles */\n\n.odoc-toc>ul>li>a {\n  font-weight: 500;\n}\n\n.odoc-toc li ul {\n  margin: 0px;\n}\n\n.odoc-toc ul {\n  list-style-type: none;\n}\n\n.odoc-toc ul li {\n  margin: 0;\n}\n.odoc-toc>ul>li {\n  margin-bottom: 0.3em;\n}\n\n.odoc-toc ul li li {\n  border-left: 1px solid var(--toc-list-border);\n  margin-left: 5px;\n  padding-left: 12px;\n}\n\n/* Mobile adjustements. */\n\n@media only screen and (max-width: 110ex) {\n  body {\n    margin: 2em;\n  }\n  .odoc-toc {\n    position: static;\n    width: auto;\n    min-width: unset;\n    max-width: unset;\n    border: none;\n    padding: 0.2em 1em;\n    border-radius: 5px;\n    margin-bottom: 2em;\n  }\n}\n\n/* Print adjustements. */\n\n@media print {\n  body {\n    color: black;\n    background: white;\n  }\n  body nav:first-child {\n    visibility: hidden;\n  }\n}\n\n/* Source code. */\n\n.source_container {\n  display: flex;\n}\n\n.source_line_column {\n  padding-right: 0.5em;\n  text-align: right;\n  background: #eee8d5;\n}\n\n.source_line {\n  padding: 0 1em;\n}\n\n.source_code {\n  flex-grow: 1;\n  background: #fdf6e3;\n  padding: 0 0.3em;\n  color: #657b83;\n}\n\n/* Source directories */\n\n.odoc-directory::before {\n  content: \"\240\159\147\129\";\n  margin: 0.3em;\n  font-size: 1.3em;\n}\n\n.odoc-file::before {\n  content: \"\240\159\147\132\";\n  margin: 0.3em;\n  font-size: 1.3em;\n}\n\n.odoc-folder-list {\n  list-style: none;\n}\n\n/* Syntax highlighting (based on github-gist) */\n\n.hljs {\n  display: block;\n  background: var(--code-background);\n  padding: 0.5em;\n  color: var(--color);\n  overflow-x: auto;\n}\n\n.hljs-comment,\n.hljs-meta {\n  color: #969896;\n}\n\n.hljs-string,\n.hljs-variable,\n.hljs-template-variable,\n.hljs-strong,\n.hljs-emphasis,\n.hljs-quote {\n  color: #df5000;\n}\n\n.hljs-keyword,\n.hljs-selector-tag {\n  color: #a71d5d;\n}\n\n.hljs-type,\n.hljs-class .hljs-title {\n  color: #458;\n  font-weight: 500;\n}\n\n.hljs-literal,\n.hljs-symbol,\n.hljs-bullet,\n.hljs-attribute {\n  color: #0086b3;\n}\n\n.hljs-section,\n.hljs-name {\n  color: #63a35c;\n}\n\n.hljs-tag {\n  color: #333333;\n}\n\n.hljs-attr,\n.hljs-selector-id,\n.hljs-selector-class,\n.hljs-selector-attr,\n.hljs-selector-pseudo {\n  color: #795da3;\n}\n\n.hljs-addition {\n  color: #55a532;\n  background-color: #eaffea;\n}\n\n.hljs-deletion {\n  color: #bd2c00;\n  background-color: #ffecec;\n}\n\n.hljs-link {\n  text-decoration: underline;\n}\n\n.VAL, .TYPE, .LET, .REC, .IN, .OPEN, .NONREC, .MODULE, .METHOD, .LETOP, .INHERIT, .INCLUDE, .FUNCTOR, .EXTERNAL, .CONSTRAINT, .ASSERT, .AND, .END, .CLASS, .STRUCT, .SIG {\n  color: #859900;;\n}\n\n.WITH, .WHILE, .WHEN, .VIRTUAL, .TRY, .TO, .THEN, .PRIVATE, .OF, .NEW, .MUTABLE, .MATCH, .LAZY, .IF, .FUNCTION, .FUN, .FOR, .EXCEPTION, .ELSE, .TO, .DOWNTO, .DO, .DONE, .BEGIN, .AS {\n  color: #cb4b16;\n}\n\n.TRUE, .FALSE {\n  color: #b58900;\n}\n\n.failwith, .INT, .SEMISEMI, .LIDENT {\n  color: #2aa198;\n}\n\n.STRING, .CHAR, .UIDENT {\n  color: #b58900;\n}\n\n.DOCSTRING {\n  color: #268bd2;\n}\n\n.COMMENT {\n  color: #93a1a1;\n}\n\n/*---------------------------------------------------------------------------\n   Copyright (c) 2016 The odoc contributors\n\n   Permission to use, copy, modify, and/or distribute this software for any\n   purpose with or without fee is hereby granted, provided that the above\n   copyright notice and this permission notice appear in all copies.\n\n   THE SOFTWARE IS PROVIDED \"AS IS\" AND THE AUTHOR DISCLAIMS ALL WARRANTIES\n   WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF\n   MERC"
-
   let d_3a50124eae7017a15bb92024b9f6c8ad = "&(t=e.gullet.popToken()),t}(t);return nr(t,n,a,\"\\\\\\\\globallet\"===r),{type:\"internal\",mode:t.mode}}}),ot({type:\"internal\",names:[\"\\\\futurelet\",\"\\\\\\\\globalfuture\"],props:{numArgs:0,allowedInText:!0,primitive:!0},handler:function(e){var t=e.parser,r=e.funcName,n=rr(t.gullet.popToken()),a=t.gullet.popToken(),i=t.gullet.popToken();return nr(t,n,i,\"\\\\\\\\globalfuture\"===r),t.gullet.pushToken(i),t.gullet.pushToken(a),{type:\"internal\",mode:t.mode}}});var ar=function(e,t,r){var n=q(ae.math[e]&&ae.math[e].replace||e,t,r);if(!n)throw new Error(\"Unsupported symbol \"+e+\" and font size \"+t+\".\");return n},ir=function(e,t,r,n){var a=r.havingBaseStyle(t),i=Ke.makeSpan(n.concat(a.sizingClasses(r)),[e],r),o=a.sizeMultiplier/r.sizeMultiplier;return i.height*=o,i.depth*=o,i.maxFontSize=a.sizeMultiplier,i},or=function(e,t,r){var n=t.havingBaseStyle(r),a=(1-t.sizeMultiplier/n.sizeMultiplier)*t.fontMetrics().axisHeight;e.classes.push(\"delimcenter\"),e.style.top=V(a),e.height-=a,e.depth+=a},sr=function(e,t,r,n,a,i){var o=function(e,t,r,n){return Ke.makeSymbol(e,\"Size\"+t+\"-Regular\",r,n)}(e,t,a,n),s=ir(Ke.makeSpan([\"delimsizing\",\"size\"+t],[o],n),x.TEXT,n,i);return r&&or(s,n,x.TEXT),s},lr=function(e,t,r){var n;return n=\"Size1-Regular\"===t?\"delim-size1\":\"delim-size4\",{type:\"elem\",elem:Ke.makeSpan([\"delimsizinginner\",n],[Ke.makeSpan([],[Ke.makeSymbol(e,t,r)])])}},hr=function(e,t,r){var n=T[\"Size4-Regular\"][e.charCodeAt(0)]?T[\"Size4-Regular\"][e.charCodeAt(0)][4]:T[\"Size1-Regular\"][e.charCodeAt(0)][4],a=new J(\"inner\",function(e,t){switch(e){case\"\\u239c\":return\"M291 0 H417 V\"+t+\" H291z M291 0 H417 V\"+t+\" H291z\";case\"\\u2223\":return\"M145 0 H188 V\"+t+\" H145z M145 0 H188 V\"+t+\" H145z\";case\"\\u2225\":return\"M145 0 H188 V\"+t+\" H145z M145 0 H188 V\"+t+\" H145zM367 0 H410 V\"+t+\" H367z M367 0 H410 V\"+t+\" H367z\";case\"\\u239f\":return\"M457 0 H583 V\"+t+\" H457z M457 0 H583 V\"+t+\" H457z\";case\"\\u23a2\":return\"M319 0 H403 V\"+t+\" H319z M319 0 H403 V\"+t+\" H319z\";case\"\\u23a5\":return\"M263 0 H347 V\"+t+\" H263z M263 0 H347 V\"+t+\" H263z\";case\"\\u23aa\":return\"M384 0 H504 V\"+t+\" H384z M384 0 H504 V\"+t+\" H384z\";case\"\\u23d0\":return\"M312 0 H355 V\"+t+\" H312z M312 0 H355 V\"+t+\" H312z\";case\"\\u2016\":return\"M257 0 H300 V\"+t+\" H257z M257 0 H300 V\"+t+\" H257zM478 0 H521 V\"+t+\" H478z M478 0 H521 V\"+t+\" H478z\";default:return\"\"}}(e,Math.round(1e3*t))),i=new K([a],{width:V(n),height:V(t),style:\"width:\"+V(n),viewBox:\"0 0 \"+1e3*n+\" \"+Math.round(1e3*t),preserveAspectRatio:\"xMinYMin\"}),o=Ke.makeSvgSpan([],[i],r);return o.height=t,o.style.height=V(t),o.style.width=V(n),{type:\"elem\",elem:o}},mr={type:\"kern\",size:-.008},cr=[\"|\",\"\\\\lvert\",\"\\\\rvert\",\"\\\\vert\"],ur=[\"\\\\|\",\"\\\\lVert\",\"\\\\rVert\",\"\\\\Vert\"],pr=function(e,t,r,n,a,i){var o,s,h,m;o=h=m=e,s=null;var c=\"Size1-Regular\";\"\\\\uparrow\"===e?h=m=\"\\u23d0\":\"\\\\Uparrow\"===e?h=m=\"\\u2016\":\"\\\\downarrow\"===e?o=h=\"\\u23d0\":\"\\\\Downarrow\"===e?o=h=\"\\u2016\":\"\\\\updownarrow\"===e?(o=\"\\\\uparrow\",h=\"\\u23d0\",m=\"\\\\downarrow\"):\"\\\\Updownarrow\"===e?(o=\"\\\\Uparrow\",h=\"\\u2016\",m=\"\\\\Downarrow\"):l.contains(cr,e)?h=\"\\u2223\":l.contains(ur,e)?h=\"\\u2225\":\"[\"===e||\"\\\\lbrack\"===e?(o=\"\\u23a1\",h=\"\\u23a2\",m=\"\\u23a3\",c=\"Size4-Regular\"):\"]\"===e||\"\\\\rbrack\"===e?(o=\"\\u23a4\",h=\"\\u23a5\",m=\"\\u23a6\",c=\"Size4-Regular\"):\"\\\\lfloor\"===e||\"\\u230a\"===e?(h=o=\"\\u23a2\",m=\"\\u23a3\",c=\"Size4-Regular\"):\"\\\\lceil\"===e||\"\\u2308\"===e?(o=\"\\u23a1\",h=m=\"\\u23a2\",c=\"Size4-Regular\"):\"\\\\rfloor\"===e||\"\\u230b\"===e?(h=o=\"\\u23a5\",m=\"\\u23a6\",c=\"Size4-Regular\"):\"\\\\rceil\"===e||\"\\u2309\"===e?(o=\"\\u23a4\",h=m=\"\\u23a5\",c=\"Size4-Regular\"):\"(\"===e||\"\\\\lparen\"===e?(o=\"\\u239b\",h=\"\\u239c\",m=\"\\u239d\",c=\"Size4-Regular\"):\")\"===e||\"\\\\rparen\"===e?(o=\"\\u239e\",h=\"\\u239f\",m=\"\\u23a0\",c=\"Size4-Regular\"):\"\\\\{\"===e||\"\\\\lbrace\"===e?(o=\"\\u23a7\",s=\"\\u23a8\",m=\"\\u23a9\",h=\"\\u23aa\",c=\"Size4-Regular\"):\"\\\\}\"===e||\"\\\\rbrace\"===e?(o=\"\\u23ab\",s=\"\\u23ac\",m=\"\\u23ad\",h=\"\\u23aa\",c=\"Size4-Regular\"):\"\\\\lgroup\"===e||\"\\u27ee\"===e?(o=\"\\u23a7\",m=\"\\u23a9\",h=\"\\u23aa\",c=\"Size4-Regular\"):\"\\\\rgroup\"===e||\"\\u27ef\"===e?(o=\"\\u23ab\",m=\"\\u23ad\",h=\"\\u23aa\",c=\"Size4-Regular\"):\"\\\\lmoustache\"===e||\"\\u23b0\"===e?(o=\"\\u23a7\",m=\"\\u23ad\",h=\"\\u23aa\",c=\"Size4-Regular\"):\"\\\\rmoustache\"!==e&&\"\\u23b1\"!==e||(o=\""
 
   let d_3a7455b94742964a6cc5e84e314a6cfb = "e,he,be,\"\\u22eb\",\"\\\\ntriangleright\"),ie(oe,he,be,\"\\u22ed\",\"\\\\ntrianglerighteq\",!0),ie(oe,he,be,\"\\ue018\",\"\\\\@nsupseteqq\"),ie(oe,he,be,\"\\u228b\",\"\\\\supsetneq\",!0),ie(oe,he,be,\"\\ue01b\",\"\\\\@varsupsetneq\"),ie(oe,he,be,\"\\u2acc\",\"\\\\supsetneqq\",!0),ie(oe,he,be,\"\\ue019\",\"\\\\@varsupsetneqq\"),ie(oe,he,be,\"\\u22ae\",\"\\\\nVdash\",!0),ie(oe,he,be,\"\\u2ab5\",\"\\\\precneqq\",!0),ie(oe,he,be,\"\\u2ab6\",\"\\\\succneqq\",!0),ie(oe,he,be,\"\\ue016\",\"\\\\@nsubseteqq\"),ie(oe,he,ce,\"\\u22b4\",\"\\\\unlhd\"),ie(oe,he,ce,\"\\u22b5\",\"\\\\unrhd\"),ie(oe,he,be,\"\\u219a\",\"\\\\nleftarrow\",!0),ie(oe,he,be,\"\\u219b\",\"\\\\nrightarrow\",!0),ie(oe,he,be,\"\\u21cd\",\"\\\\nLeftarrow\",!0),ie(oe,he,be,\"\\u21cf\",\"\\\\nRightarrow\",!0),ie(oe,he,be,\"\\u21ae\",\"\\\\nleftrightarrow\",!0),ie(oe,he,be,\"\\u21ce\",\"\\\\nLeftrightarrow\",!0),ie(oe,he,be,\"\\u25b3\",\"\\\\vartriangle\"),ie(oe,he,xe,\"\\u210f\",\"\\\\hslash\"),ie(oe,he,xe,\"\\u25bd\",\"\\\\triangledown\"),ie(oe,he,xe,\"\\u25ca\",\"\\\\lozenge\"),ie(oe,he,xe,\"\\u24c8\",\"\\\\circledS\"),ie(oe,he,xe,\"\\xae\",\"\\\\circledR\"),ie(se,he,xe,\"\\xae\",\"\\\\circledR\"),ie(oe,he,xe,\"\\u2221\",\"\\\\measuredangle\",!0),ie(oe,he,xe,\"\\u2204\",\"\\\\nexists\"),ie(oe,he,xe,\"\\u2127\",\"\\\\mho\"),ie(oe,he,xe,\"\\u2132\",\"\\\\Finv\",!0),ie(oe,he,xe,\"\\u2141\",\"\\\\Game\",!0),ie(oe,he,xe,\"\\u2035\",\"\\\\backprime\"),ie(oe,he,xe,\"\\u25b2\",\"\\\\blacktriangle\"),ie(oe,he,xe,\"\\u25bc\",\"\\\\blacktriangledown\"),ie(oe,he,xe,\"\\u25a0\",\"\\\\blacksquare\"),ie(oe,he,xe,\"\\u29eb\",\"\\\\blacklozenge\"),ie(oe,he,xe,\"\\u2605\",\"\\\\bigstar\"),ie(oe,he,xe,\"\\u2222\",\"\\\\sphericalangle\",!0),ie(oe,he,xe,\"\\u2201\",\"\\\\complement\",!0),ie(oe,he,xe,\"\\xf0\",\"\\\\eth\",!0),ie(se,le,xe,\"\\xf0\",\"\\xf0\"),ie(oe,he,xe,\"\\u2571\",\"\\\\diagup\"),ie(oe,he,xe,\"\\u2572\",\"\\\\diagdown\"),ie(oe,he,xe,\"\\u25a1\",\"\\\\square\"),ie(oe,he,xe,\"\\u25a1\",\"\\\\Box\"),ie(oe,he,xe,\"\\u25ca\",\"\\\\Diamond\"),ie(oe,he,xe,\"\\xa5\",\"\\\\yen\",!0),ie(se,he,xe,\"\\xa5\",\"\\\\yen\",!0),ie(oe,he,xe,\"\\u2713\",\"\\\\checkmark\",!0),ie(se,he,xe,\"\\u2713\",\"\\\\checkmark\"),ie(oe,he,xe,\"\\u2136\",\"\\\\beth\",!0),ie(oe,he,xe,\"\\u2138\",\"\\\\daleth\",!0),ie(oe,he,xe,\"\\u2137\",\"\\\\gimel\",!0),ie(oe,he,xe,\"\\u03dd\",\"\\\\digamma\",!0),ie(oe,he,xe,\"\\u03f0\",\"\\\\varkappa\"),ie(oe,he,ge,\"\\u250c\",\"\\\\@ulcorner\",!0),ie(oe,he,ue,\"\\u2510\",\"\\\\@urcorner\",!0),ie(oe,he,ge,\"\\u2514\",\"\\\\@llcorner\",!0),ie(oe,he,ue,\"\\u2518\",\"\\\\@lrcorner\",!0),ie(oe,he,be,\"\\u2266\",\"\\\\leqq\",!0),ie(oe,he,be,\"\\u2a7d\",\"\\\\leqslant\",!0),ie(oe,he,be,\"\\u2a95\",\"\\\\eqslantless\",!0),ie(oe,he,be,\"\\u2272\",\"\\\\lesssim\",!0),ie(oe,he,be,\"\\u2a85\",\"\\\\lessapprox\",!0),ie(oe,he,be,\"\\u224a\",\"\\\\approxeq\",!0),ie(oe,he,ce,\"\\u22d6\",\"\\\\lessdot\"),ie(oe,he,be,\"\\u22d8\",\"\\\\lll\",!0),ie(oe,he,be,\"\\u2276\",\"\\\\lessgtr\",!0),ie(oe,he,be,\"\\u22da\",\"\\\\lesseqgtr\",!0),ie(oe,he,be,\"\\u2a8b\",\"\\\\lesseqqgtr\",!0),ie(oe,he,be,\"\\u2251\",\"\\\\doteqdot\"),ie(oe,he,be,\"\\u2253\",\"\\\\risingdotseq\",!0),ie(oe,he,be,\"\\u2252\",\"\\\\fallingdotseq\",!0),ie(oe,he,be,\"\\u223d\",\"\\\\backsim\",!0),ie(oe,he,be,\"\\u22cd\",\"\\\\backsimeq\",!0),ie(oe,he,be,\"\\u2ac5\",\"\\\\subseteqq\",!0),ie(oe,he,be,\"\\u22d0\",\"\\\\Subset\",!0),ie(oe,he,be,\"\\u228f\",\"\\\\sqsubset\",!0),ie(oe,he,be,\"\\u227c\",\"\\\\preccurlyeq\",!0),ie(oe,he,be,\"\\u22de\",\"\\\\curlyeqprec\",!0),ie(oe,he,be,\"\\u227e\",\"\\\\precsim\",!0),ie(oe,he,be,\"\\u2ab7\",\"\\\\precapprox\",!0),ie(oe,he,be,\"\\u22b2\",\"\\\\vartriangleleft\"),ie(oe,he,be,\"\\u22b4\",\"\\\\trianglelefteq\"),ie(oe,he,be,\"\\u22a8\",\"\\\\vDash\",!0),ie(oe,he,be,\"\\u22aa\",\"\\\\Vvdash\",!0),ie(oe,he,be,\"\\u2323\",\"\\\\smallsmile\"),ie(oe,he,be,\"\\u2322\",\"\\\\smallfrown\"),ie(oe,he,be,\"\\u224f\",\"\\\\bumpeq\",!0),ie(oe,he,be,\"\\u224e\",\"\\\\Bumpeq\",!0),ie(oe,he,be,\"\\u2267\",\"\\\\geqq\",!0),ie(oe,he,be,\"\\u2a7e\",\"\\\\geqslant\",!0),ie(oe,he,be,\"\\u2a96\",\"\\\\eqslantgtr\",!0),ie(oe,he,be,\"\\u2273\",\"\\\\gtrsim\",!0),ie(oe,he,be,\"\\u2a86\",\"\\\\gtrapprox\",!0),ie(oe,he,ce,\"\\u22d7\",\"\\\\gtrdot\"),ie(oe,he,be,\"\\u22d9\",\"\\\\ggg\",!0),ie(oe,he,be,\"\\u2277\",\"\\\\gtrless\",!0),ie(oe,he,be,\"\\u22db\",\"\\\\gtreqless\",!0),ie(oe,he,be,\"\\u2a8c\",\"\\\\gtreqqless\",!0),ie(oe,he,be,\"\\u2256\",\"\\\\eqcirc\",!0),ie(oe,he,be,\"\\u2257\",\"\\\\circeq\",!0),ie(oe,he,be,\"\\u225c\",\"\\\\triangleq\",!0),ie(oe,he,be,\"\\u223c\",\"\\\\thicksim\"),ie(oe,he,be,\"\\u2248\",\"\\\\thickapprox\"),ie(oe,he,be,\"\\u2ac6\",\"\\\\supseteqq\",!0),ie(oe,he,be,\"\\u22d1\",\"\\\\Supset\",!0),ie(oe,he,be,\"\\u2290\",\"\\\\sqsupset\",!0),ie(oe,he,be,\"\\u227d\",\"\\\\succcurlyeq\",!0),ie(oe,he,be,\"\\u22df\",\"\\\\curlyeqsucc"
 
+  let d_4022f9ddc62af63e4eed2e4c7fc5c582 = "this permission notice appear in all copies.\n\n   THE SOFTWARE IS PROVIDED \"AS IS\" AND THE AUTHOR DISCLAIMS ALL WARRANTIES\n   WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF\n   MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR\n   ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES\n   WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN\n   ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF\n   OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.\n  ---------------------------------------------------------------------------*/\n"
+
   let d_41cfd166777ab1d0e6a6b39070fbb41c = " > code, li a > code {\n  color: var(--link-color);\n}\n\n.odoc code {\n  white-space: pre-wrap;\n}\n\n/* Code blocks (e.g. Examples) */\n\n.odoc pre code {\n  font-size: 0.893rem;\n}\n\n/* Code lexemes */\n\n.keyword {\n  font-weight: 500;\n}\n\n.arrow { white-space: nowrap }\n\n/* Module member specification */\n\n.spec {\n  background-color: var(--spec-summary-background);\n  border-radius: 3px;\n  border-left: 4px solid var(--spec-summary-border-color);\n  border-right: 5px solid transparent;\n  padding: 0.35em 0.5em;\n}\n\nli:not(:last-child) > .def-doc {\n  margin-bottom: 15px;\n}\n\n/* Spacing between items */\ndiv.odoc-spec,.odoc-include {\n  margin-bottom: 2em;\n}\n\n.spec.type .variant p, .spec.type .record p {\n  margin: 5px;\n}\n\n.spec.type .variant, .spec.type .record {\n  margin-left: 2ch;\n  list-style: none;\n  display: flex;\n  flex-wrap: wrap;\n  row-gap: 4px;\n}\n\n.spec.type .record > code, .spec.type .variant > code {\n  min-width: 40%;\n}\n\n.spec.type > ol {\n  margin-top: 0;\n  margin-bottom: 0;\n}\n\n.spec.type .record > .def-doc, .spec.type .variant > .def-doc {\n  min-width:50%;\n  padding: 0.25em 0.5em;\n  margin-left: 10%;\n  border-radius: 3px;\n  flex-grow:1;\n  background: var(--main-background);\n  box-shadow: 2px 2px 4px lightgrey;\n}\n\ndiv.def {\n  margin-top: 0;\n  text-indent: -2ex;\n  padding-left: 2ex;\n}\n\ndiv.def-doc>*:first-child {\n  margin-top: 0;\n}\n\n/* Collapsible inlined include and module */\n\n.odoc-include details {\n  position: relative;\n}\n\n.odoc-include.shadowed-include {\n  display: none;\n}\n\n.odoc-include details:after {\n  z-index: -100;\n  display: block;\n  content: \" \";\n  position: absolute;\n  border-radius: 0 1ex 1ex 0;\n  right: -20px;\n  top: 1px;\n  bottom: 1px;\n  width: 15px;\n  background: var(--spec-details-after-background, rgba(0, 4, 15, 0.05));\n  box-shadow: 0 0px 0 1px var(--spec-details-after-shadow, rgba(204, 204, 204, 0.53));\n}\n\n.odoc-include summary {\n  position: relative;\n  margin-bottom: 1em;\n  cursor: pointer;\n  outline: none;\n}\n\n.odoc-include summary:hover {\n  background-color: var(--spec-summary-hover-background);\n}\n\n/* FIXME: Does not work in Firefox. */\n.odoc-include summary::-webkit-details-marker {\n  color: #888;\n  transform: scaleX(-1);\n  position: absolute;\n  top: calc(50% - 5px);\n  height: 11px;\n  right: -29px;\n}\n\n/* Records and variants FIXME */\n\ndiv.def table {\n  text-indent: 0em;\n  padding: 0;\n  margin-left: -2ex;\n}\n\ntd.def {\n  padding-left: 2ex;\n}\n\ntd.def-doc *:first-child {\n  margin-top: 0em;\n}\n\n/* Lists of @tags */\n\n.at-tags { list-style-type: none; margin-left: -3ex; }\n.at-tags li { padding-left: 3ex; text-indent: -3ex; }\n.at-tags .at-tag { text-transform: capitalize }\n\n/* Alert emoji */\n\n.alert::before, .deprecated::before {\n  content: '\226\154\160\239\184\143 ';\n}\n\n/* Lists of modules */\n\n.modules { list-style-type: none; margin-left: -3ex; }\n.modules li { padding-left: 3ex; text-indent: -3ex; margin-top: 5px }\n.modules .synopsis { padding-left: 1ch; }\n\n/* Odig package index */\n\n.packages { list-style-type: none; margin-left: -3ex; }\n.packages li { padding-left: 3ex; text-indent: -3ex }\n.packages li a.anchor { padding-right: 0.5ch; padding-left: 3ch; }\n.packages .version { font-size: 10px; color: var(--by-name-version-color); }\n.packages .synopsis { padding-left: 1ch }\n\n.by-name nav a {\n  text-transform: uppercase;\n  font-size: 18px;\n  margin-right: 1ex;\n  color: var(--by-name-nav-link-color,);\n  display: inline-block;\n}\n\n.by-tag nav a {\n  margin-right: 1ex;\n  color: var(--by-name-nav-link-color);\n  display: inline-block;\n}\n\n.by-tag ol { list-style-type: none; }\n.by-tag ol.tags li { margin-left: 1ch; display: inline-block }\n.by-tag td:first-child { text-transform: uppercase; }\n\n/* Odig package page */\n\n.package nav {\n  display: inline;\n  font-size: 14px;\n  font-weight: normal;\n}\n\n.package .version {\n  font-size: 14px;\n}\n\n.package.info {\n  margin: 0;\n}\n\n.package.info td:first-child {\n  font-style: italic;\n  padding-right: 2ex;\n}\n\n.package.info ul {\n  list-style-type: none;\n  display: inline;\n  margin: 0;\n}\n\n.package.info li {\n  display: inline-block;\n  margin: 0;\n  margin-right: 1ex;\n}\n\n#info-authors li, #info-maintainers li {\n  disp"
 
   let d_428c2b0f069b4ffaef294dc85aef1e4b = "Er(\"\\\\maroonB\",\"\\\\textcolor{##ff92c6}{#1}\"),Er(\"\\\\maroonC\",\"\\\\textcolor{##ed5fa6}{#1}\"),Er(\"\\\\maroonD\",\"\\\\textcolor{##ca337c}{#1}\"),Er(\"\\\\maroonE\",\"\\\\textcolor{##9e034e}{#1}\"),Er(\"\\\\purpleA\",\"\\\\textcolor{##ddd7ff}{#1}\"),Er(\"\\\\purpleB\",\"\\\\textcolor{##c6b9fc}{#1}\"),Er(\"\\\\purpleC\",\"\\\\textcolor{##aa87ff}{#1}\"),Er(\"\\\\purpleD\",\"\\\\textcolor{##7854ab}{#1}\"),Er(\"\\\\purpleE\",\"\\\\textcolor{##543b78}{#1}\"),Er(\"\\\\mintA\",\"\\\\textcolor{##f5f9e8}{#1}\"),Er(\"\\\\mintB\",\"\\\\textcolor{##edf2df}{#1}\"),Er(\"\\\\mintC\",\"\\\\textcolor{##e0e5cc}{#1}\"),Er(\"\\\\grayA\",\"\\\\textcolor{##f6f7f7}{#1}\"),Er(\"\\\\grayB\",\"\\\\textcolor{##f0f1f2}{#1}\"),Er(\"\\\\grayC\",\"\\\\textcolor{##e3e5e6}{#1}\"),Er(\"\\\\grayD\",\"\\\\textcolor{##d6d8da}{#1}\"),Er(\"\\\\grayE\",\"\\\\textcolor{##babec2}{#1}\"),Er(\"\\\\grayF\",\"\\\\textcolor{##888d93}{#1}\"),Er(\"\\\\grayG\",\"\\\\textcolor{##626569}{#1}\"),Er(\"\\\\grayH\",\"\\\\textcolor{##3b3e40}{#1}\"),Er(\"\\\\grayI\",\"\\\\textcolor{##21242c}{#1}\"),Er(\"\\\\kaBlue\",\"\\\\textcolor{##314453}{#1}\"),Er(\"\\\\kaGreen\",\"\\\\textcolor{##71B307}{#1}\");var Vn={\"^\":!0,_:!0,\"\\\\limits\":!0,\"\\\\nolimits\":!0},Gn=function(){function e(e,t,r){this.settings=void 0,this.expansionCount=void 0,this.lexer=void 0,this.macros=void 0,this.stack=void 0,this.mode=void 0,this.settings=t,this.expansionCount=0,this.feed(e),this.macros=new On(Hn,t.macros),this.mode=r,this.stack=[]}var t=e.prototype;return t.feed=function(e){this.lexer=new Rn(e,this.settings)},t.switchMode=function(e){this.mode=e},t.beginGroup=function(){this.macros.beginGroup()},t.endGroup=function(){this.macros.endGroup()},t.endGroups=function(){this.macros.endGroups()},t.future=function(){return 0===this.stack.length&&this.pushToken(this.lexer.lex()),this.stack[this.stack.length-1]},t.popToken=function(){return this.future(),this.stack.pop()},t.pushToken=function(e){this.stack.push(e)},t.pushTokens=function(e){var t;(t=this.stack).push.apply(t,e)},t.scanArgument=function(e){var t,r,n;if(e){if(this.consumeSpaces(),\"[\"!==this.future().text)return null;t=this.popToken();var a=this.consumeArg([\"]\"]);n=a.tokens,r=a.end}else{var i=this.consumeArg();n=i.tokens,t=i.start,r=i.end}return this.pushToken(new Dr(\"EOF\",r.loc)),this.pushTokens(n),t.range(r,\"\")},t.consumeSpaces=function(){for(;;){if(\" \"!==this.future().text)break;this.stack.pop()}},t.consumeArg=function(e){var t=[],r=e&&e.length>0;r||this.consumeSpaces();var a,i=this.future(),o=0,s=0;do{if(a=this.popToken(),t.push(a),\"{\"===a.text)++o;else if(\"}\"===a.text){if(-1===--o)throw new n(\"Extra }\",a)}else if(\"EOF\"===a.text)throw new n(\"Unexpected end of input in a macro argument, expected '\"+(e&&r?e[s]:\"}\")+\"'\",a);if(e&&r)if((0===o||1===o&&\"{\"===e[s])&&a.text===e[s]){if(++s===e.length){t.splice(-s,s);break}}else s=0}while(0!==o||r);return\"{\"===i.text&&\"}\"===t[t.length-1].text&&(t.pop(),t.shift()),t.reverse(),{tokens:t,start:i,end:a}},t.consumeArgs=function(e,t){if(t){if(t.length!==e+1)throw new n(\"The length of delimiters doesn't match the number of args!\");for(var r=t[0],a=0;a<r.length;a++){var i=this.popToken();if(r[a]!==i.text)throw new n(\"Use of the macro doesn't match its definition\",i)}}for(var o=[],s=0;s<e;s++)o.push(this.consumeArg(t&&t[s+1]).tokens);return o},t.expandOnce=function(e){var t=this.popToken(),r=t.text,a=t.noexpand?null:this._getExpansion(r);if(null==a||e&&a.unexpandable){if(e&&null==a&&\"\\\\\"===r[0]&&!this.isDefined(r))throw new n(\"Undefined control sequence: \"+r);return this.pushToken(t),t}if(this.expansionCount++,this.expansionCount>this.settings.maxExpand)throw new n(\"Too many expansions: infinite loop or need to increase maxExpand setting\");var i=a.tokens,o=this.consumeArgs(a.numArgs,a.delimiters);if(a.numArgs)for(var s=(i=i.slice()).length-1;s>=0;--s){var l=i[s];if(\"#\"===l.text){if(0===s)throw new n(\"Incomplete placeholder at end of macro body\",l);if(\"#\"===(l=i[--s]).text)i.splice(s+1,1);else{if(!/^[1-9]$/.test(l.text))throw new n(\"Not a valid argument number\",l);var h;(h=i).splice.apply(h,[s,2].concat(o[+l.text-1]))}}}return this.pushTokens(i),i},t.expandAfterFuture=function(){return this.expandOnce(),this.future()},t.expandNextToken=function(){for(;;){var e=this.expandOnce();if(e instan"
@@ -120,6 +120,8 @@ module Internal = struct
 
   let d_6da4435aa78c6d4454355dfa135298c4 = "\253\022\231E\137#9]\158\0272yP\003!\236\244\019\137\193\184\146\133\1392jc\234\179\204\217\190\244\142\020\241\141\198\215\195d\244~\215M\175\211\227\226EG\188;\233\160\170\160\2117\014\027J\t\246^\196\219Y\247?\143\131T2,\179u\134\155\184\254\154A4\146B\014\254w3]\029\t\169\244\225\216q\018]\194\211,X\226X\234ld\177{F\017<\198\018\020k\002\129h\197\224\142|\241\191M\2329c\209f<\229\178?\205\004Y\175\142\241_M\007\141\170h\026\247\233\140\017\172\024\240\022\161\140\225\138\165\142%\133\005\141\132r0r\000%H\186&9\236\229\255\019'$\015X\191\151$\163s \221sq\206\209\182K0N\167\205\139)x.\207n\027m\167*=\209\225a\006\005\027\143\130\018\216?\165\150\223&7Gq\019w\232S\243T\n\253P\1728s\247Y\239\141\236n\149\030s\011\029\191\169]\195\000\001\224\244\216X\229\141\221\185c\243\011\028\1379%\184\159*3\023i$R\\\143q{\150\250\186H\254\234\242\249\181\170\220\164\234\242\2483\153\163\206\2484\213\171[L\183DE\211\167\132\248&e\230\210H\180>c]\1765W6%~f\190C\153\167i\026f\2152\149\203\143\\\153\201\238 |5\127\179\214\b\147\183l\231\179\020_\164\1809\138\149T\018\251h&\163\252f9\003{K\214\149\031e\232\248\030\216\012\183$7\027A\012\206\212\167\128\179ib\183\198\180O/\2151\159t\204~\194\210q\221$,\246\136\221\223\167\167\163tuU\173\136\174[S\017^R\147nXe\\\r55c\253\227\214\169\251\148\186kW\193\2492jY\253\169pS h\227/w1\026\243o\208I\177\248z]\177\147y\254\0190\162S\246\169\215M\187\152\148\236X\003Ik\163je\240\185h\245\140\025\197\197`XQ\023\024gpJ\005i\025\133?4\130\198\005\011!\138\012V\027\226\132\239\024sY+@\136O+\031\179 (\188\018\165Y5A\184v\0151\rS)\153x\239\186\189\019D\175)\2480\"\025\206\225\004o\140\2364A~\132\017\146\132T!\022\022\200\159\220\021\029\217\234r\021\020\236\233\213\184~\232rxr\199\180\178\2219\020#\132\206\214z\184\251AG\176N0w\023w\028\165\163\184\227\023o\029C\156\191\n\174\233\234\194\178`1\144\003\145\158\195\148\200`\201pg\169\205K\141\202\183\030m\138\159>\241\0126\171\029\226\229f\020\141\219\205\237\166ii0\193\030mw\006h\203\210\027;\251b\161\169\189f+\248\230D\170T\160\149h\005\210\212\019\223X\129y\254\000\132\168\130:S\197\157\213\214\004\238\199\011S!D\139\192\2094\018\201U\025@;]'\241Qg\005>\252\174\157\031\\Y\163\143\015\170\016h\246\172\228e\197\200NB\136\243*$v\"\197\203\146\251\192\172\201\175\014o\213\132\2338\203\023\205R\177a\190t?\135w\r\178\172,\246\207?\195\152\142\199\138\026C\1814\135\016\218\231\213\224F\210_o\211\154+4\206\227\161\141\222|\143oB\146;v8\214\152\252g\199\175\0252\029:km\177\225\127a\213\183\207\209\006z\167F\188\170\1716\1809\170\004\223\245\241#\006\192@\246\145Fs~\197~e\235D1\219\143zH\177\136\244\028\221\030#\210\177\139\rE\226\031\026\208\178\195aF\185\228\182CA\188S,\225\245_m\203\129\"\141l\159J\154\162c\171d\024\163\\Ef\134\2358E\203X\029\"\128\195\152\014g\199\206\128~`l\158\016\240\160\179\1452O\2304\026+\210\164\253\015 \145\196\140C\027\193\250\225\197\195K(R,z\031\174\133h:\022\220\133\029f`\254\195\016\170\227y\145c\206#\007\224/r\2026\127*]&\212a\240\163G\002=s\170\157\173\195t2T\243n\254\228\146~\199\253\1817\190\170\169VO\221:<U\2133\140\236[Irta\154\173\135_M\006b\t\140\168\130n\207\170\173\150|V\014]\171\134\005\002:)\006$\157\144Zk\206G\161\189\205\232\188\163\129B\143\011\238E\020\222u\026\219\218i\221\236\2157\191~\181\200\243\189\181\020\252]\1559E\145\242}+\tU\184s\000\247X\014B\232\152\023\154[/`:\194\129\188\208\160[\133\163h\203\179\194t\183U\248\254?\131\211\143\186\157j;\204\222\011F64_`\162\193A\143\130\024\173\210\196\227\171BK\243<4\000w\246\202\129\222\r\174\185\248\191!YC\027\190v+\217\145\0197\016h\251\186\198\155Y\131\245\017\227\202=\254{\182\000\175\155\248W:;Zk\203u\1823\189yi\255k\014`\217\"\191\131\155m+\221\147\150'X\139\165\224\199\218\233s\181>\250\164r\142],\018\138?\168)z\030l\004\213S&\147\247u\162T\190\170}\148\140\211GBw\162\213\139\023{\242\253v\186\217\150\155t\001\155#\028:\255\1915J\140;\193\030\194\240J\173'\184\019]\197\203\150]\134\174y\206'F\139\148\028&\189\017\242$\215\238\011P\177\131'\191\248\145?\188av\185\198\166!Z\237{+O\244\186\130\219\151&\023\167\004\2039\181\\[\021Wh+\221t\169=\212I\131a8:\152-<D\t7\b\149\251\246\"\172\237\217\172\001\188\178\188{\018\168\020\195WU\213I\220\"\026;5X\188\028\183\226\184\170\203\019\131\219\016j\026\210`\163\027\184t\238~S\012\187\153\203\233aE\197\r\189\150\173\164\139\218d`Zph\254\154a\027\176\207\001\253\158\140\206\156U<\159[\238o(\209\148\243\253\208\185h\245\220\185\233y\030\206~\176O\171\192\202\158\132\024\229]\14151\215\158\218\227\019\220\241\171\162\192\138\188F\199\168\204\209#\221\218B\232{U\129\251\221d\245\017\252|\127\017\"\217)\n|F\177\1820:\217nOQI~ZYL\185I\219\188\156VOQyG\014oX\214nKs\226\201\213\018\b\199\024\161\137\147!\001\137\170OA\196C\024m@_\191?iQ\132Bk\023\209*\156\169a\226\237ZH(\152\n\027\205r\029\215\238\182sur\179\017\158*\016B\218\237\226\176\164e\187\231\254\201h\167\016T;*\012~\227Q*f\141\186n%~=\149\239\127\215|\243L\160\2130/\220\153?/\174\200\147\192l\003\004\225\133\211:B\182\255LH\019N\199\192=\180s\204~\1295B\199\1887~J\017['\188\179\207\136\192\199~\132\246\223fP+\191\127l\005\215\151l\255\221\200\240\150A\143j\128\166\019\135\017B\003\161\134\254\003dk\254QT\199\25354Y\019]g\168\137'\156\004\025Ml\248\014\212\228\255\150z\1402\011@\n\1846Y]\190\245\127\209\132\1429\028\154\244\152\173\227\234\254\191\028\165\229\253\224}\158u\193z\019\022\230\132\214\223\t\215a\247\218{\237,\029\215C\174\254l\241\017\001L\253\213\207\214\161\188\011=\245G1\029Q\006\255\158\178\2497\b>\"T\201\205<\129\142\249d\194\244\"\182\142N\172\023 \147N\193P\203V\168\226\230\163'\152\142y@F\000&U\174V[\179\222\231\205l\213\148\227\181\145e\211\234%tI\024\136\1673'GElzZ\244\212\214\000\003\006\239u\000\211\161\232\175}3\227b&[\167F\181\1827\031lyGu_/\020\140\137_;\250\250e@\254\172\131\131KCK\242f\229\247C$3\226\127L\029s[\189\203\192\208\241\139\144\131\160zK\229\186\2146*\230\222\147$\145\014u\158b\178n\132}\018\226\242\001\217\029 \194\211\202@\159\021sX\174V\1609L-\006\241i\b\246\203\207@\025\197\229Qg\018N\198@\203\206\229\209\188.\150\199\"\128\005\232\196?\190[\160\173[[\167E-_P\020\187\220,\188\248!\131y\018Kdu\018\021^\214.h\241W\029\250\225\244\189\147gO\131KZn\025j\242\199_\223\211<\145\184}k\157\t\205\210\252\166A\135\244\186\135\"^\231\245\252\136T{m\198O\249p]=\200\025\205\227\142\174\140\143\210\1980D\011_)\165\245\1734\149\192\132\217\146\003\241\255\235\162\146\154\155\229\014y\027\157'R\213,\019j\028Xu\132h\197\182t\b\193\0071\141g\135T\245\143Z\187\180_\132\t\247\211V\176`d\205ZH\169\026WD>qs\171\167\148Q\145\028\127\215\248P~{\243096\007\202\209\011\226\018\017\213X\136\020\139\205\146.\134{]\233/\238\135\207/\146V\215\212\137G\173\222\247\n\176.C\194}\145\248\165\019\234[!6\221~9\190\232\229\"\1514v\229\027q1\151\023B\168\001\131\167\210x\165\222HM\162'\163\204\252\214\t>&\2443:[\232\208\242\196h\188\014\203\1737\194\234\177\016\169\131W2\245\012\203\164\165\185\238\234\017n\025#\172n\218\236\018\239\178\230\214\197\203\1627\248\145\211P\188\000weMX\251(I\253Z\145\130m~\197h\150\241\189)\234\220\178\248\219\166w\227B\\\001\139\166U\023\217GQs\135\202\003\177\1994Ucf\0220\245\172\202\234\246\128\r\027k\021\213\223I\230g\1511>\194\br\\\253\189w;)\238\031\163\237\219<:\143\029\216\165\191\007\028W @W\254\161\018\159\214\157\022\147B\218\236\243\221\173\155\138\129\215>A7v\235v\200\210\185bk\164\014\205Y{:M\250@\134\155pE~\132\027\130 \189\181;\187\007&HL\031\187[\231\172\213\199\239 \213\203\230\129G\197\160\167\003\167\170\197\020)\1887#\189\160\232\163\251w\132\252\216\231/\025\187\178RtWN[\226v\023\228i\146L'\223\157f\022\235\020\029\222$\167\226\140=bY^\210w\163\171[L\017\142\203\169MB\182v\210$7\165TP\158\249\205\002\174\138%\219O_\193\130\016O\166\183h\026\187\003\157\219\007\205\136c\227:\236\194\149\011\152\014\199Rph\016\204gLx\174H$TAHM\151\240\149L!\003mE\006=;\140\025\030\rL\025a\154b`\179( \027\159\023\237\223\248I|></hKY02=\247\227\195b\029\182}t%IX\139\165\171\211\186M\236\142c\192\182\020*xA_\199\130h0\248\146\023\175``Tj\162C\023+\190\175{)\150v\127\140r\25073r\1946\210M\235q\129X\028\128/\212g\224\219\227\199S\2020\210N\2151/\1803j9\138e\016]\199u\210\158\230f\209\160\153\031\180\222K\140d\235\208\163y\245\0230\029\163\147`\152\163F/\128N~\181:5\221\240\218\237\151\182\015j}\186a\172\029\157\1598l?}9\011F22\133\005Y\213Q~\215[\203\014\209\150}pj\163!\144\226k\168\133\1339\130\025\170$\231\012[\151\195\230\245d\180\206\247\199\003\134\227\005\145\192-\022k\210\208\133\176\199j\208\245\208\207\151\176O*\187\251\253\204_\152\165o]\189\006\129\247?eU?5E\200\155\188\228\232)\020z@*?0\141\229't51\127\231N\221\161\176\185ob\194C\222\250\\\1481'\221\200\023\r\187\184\163{K\169H\166\2137\250\202\231\ng\198\164P)\212\235\192\012)\148\144\152\"Qy\211A\004\180\254\026\027\030\2381Y\127\210z<q\130\210\006Wf\219\030=\214\163?\157\159Z\158\177\240\255C\1741\185+\162\229\181v\206\252R\232\247\2235r\005\224\018A\149p0\162\204\193F\014\195G\180\246sn\187\165\253@\128\224\251\157|E.>y\201\178\187\146\254\023\029\158\222\160\017}\021wCDL\165 \194\245\255I\019\233\1651h87\130N\162\244\004\0140\147\031[\167\156\173\174\246\136\209\249KMt\134\174\219Pe\227R\003\239}\182 \239\005\225\164\147\158\160\1997\234\216\164\193Pp\031\198\b\021Zi\006\156\199u\196O\148\171\178\234\n\"\136_\215 O\167\166\217\228\239 \236\238E\\\131A\251\224\217\252\235\243\152#;7\020\030B\023\149\242\181\031\012\232\006\150\129\233\160zD\157\192t3\162\213Z\181\206\177\199\022o\254\211\142.^P\168a\2187>t\184\188z\161\142\131\019t/\017\021\174\221\192\244C|C\130\001\231\171N\143\209\163\239\141\149\242\240\175\015\215\242\182h\149\213\165[\129\130\217`,\211\179\197\200\022\139\209\192![|TZ']\199\238\018P\253\001A\142\128\202Y\216JK{v\164C\162C\151\151\214<\193t\188\218D\154q\142q\142\188 c\011\134\175\192i:\244b\159\030\199\202\223\n\180\147b{Q\226\130\001\2111.\0209\139\232:\020\218\138<\253s\162\223BRf\1444\1448/\248l\181\155\164,\179\187\218_m\021\233\208\237\129\n\192\151\206\000\031\138\159\021?\0039D,T5\249\023\168\007q\129\014]\238\173\186\199\208\161\215\158\004\189\219Q\029\207M\003\166\023_\166\229\167\251\137A\018\189\027\174c\024\028\t)\001L\151\204F\178J'\207\222\134\152\153\248\251\184AO\2151.\148\248\250\209\134Y\254\25244\179\2372\249*3h-%^f\016\251\159q%U$S\135\176+P\200?\030\140\n\168\205\024\251'\022,\022\163I\182\1843B\222\031;\012\134\006.\255\147/-*\150\231}\239\169\241\137L\190\142\177=T\rc:f\018\209\248\022J\236\140\239d\226]$\162Cg\251,\195t\029\187GE\020\1276\250\135o\199TZ\241Xk\140\024\141Ea\230z\024\011\134X\028\192@\237\149\127\246\031\2539\171kOZ\030Z\024\t\t\004(\196?\r\208w\015\001e\020\147\011\bZ\019\153n\007\180y\015&\161\133L-z\228)7D\250\198\026/\139\192\002\161\002\148\165\003\232?\142\132XvH\022b\199:\018\254\147\193\004\019\193\160hV\207\2332\020\174E\005!\014WE\242\186|YE\190\129~:3\127\156j\188\006\243\210\251\007|\027\028\234\217<R\133\174y#\027\247\020|;]:\172\235\168\245\011n\n\139\233oK\185\167\005<\198\n\151)\001x\n1\206\248w|,\208\003\022\188\022\165\184\147\141\185\185\236\020\204\224\142\221B\003\131`\128(j\nca\181\231\1641\210+H\223\226\214\026\176\020tq\210h\177\240\2526\137zc\243\151_@\022T;B\136\183\029Y\2547\255.\250w\030yL\141\011\002dA~\226\228\230(\150(5#oT\1555\154\148<\014\248\025M\185q\153\142\135\209\137\239\193PBB\bF\150\000\213h\170\200\186&+8\161\210\226\133zV\157\250q\132\224\235\231\159]\150\238\224K0X,\025]\156)\229\031:?\246\190\1493\155Jz\158\135!\2109^\163\145\012\226z\024\194em\130\1605d~%\146\018\184\240\137n/\230Te\228\151O\022k\173\177\255\\\151Q\165\0201\153\148\1590(\205\236\254uJk\156.\201\211\021}\200yG\158\164\2434\028w'T:HkI\149M\243\211\139^M\235]\237\242G?d\191\134\229$f8V\174"
 
+  let d_702eeb76f1c77cb926fb148aa0d2af83 = "lay: block;\n}\n\n/* Sidebar and TOC */\n\n.odoc-toc:before {\n  display: block;\n  content: \"Contents\";\n  text-transform: uppercase;\n  font-size: 1em;\n  margin: 1.414em 0 0.5em;\n  font-weight: 500;\n  color: var(--toc-before-color);\n  line-height: 1.2;\n}\n\n.odoc-toc {\n  position: fixed;\n  top: 0px;\n  bottom: 0px;\n  left: 0px;\n  max-width: 30ex;\n  min-width: 26ex;\n  width: 20%;\n  background: var(--toc-background);\n  overflow: auto;\n  color: var(--toc-color);\n  padding-left: 2ex;\n  padding-right: 2ex;\n}\n\n.odoc-toc ul li a {\n  font-family: \"Fira Sans\", sans-serif;\n  font-size: 0.95em;\n  color: var(--color);\n  font-weight: 400;\n  line-height: 1.6em;\n  display: block;\n}\n\n.odoc-toc ul li a:hover {\n  box-shadow: none;\n  text-decoration: underline;\n}\n\n/* First level titles */\n\n.odoc-toc>ul>li>a {\n  font-weight: 500;\n}\n\n.odoc-toc li ul {\n  margin: 0px;\n}\n\n.odoc-toc ul {\n  list-style-type: none;\n}\n\n.odoc-toc ul li {\n  margin: 0;\n}\n.odoc-toc>ul>li {\n  margin-bottom: 0.3em;\n}\n\n.odoc-toc ul li li {\n  border-left: 1px solid var(--toc-list-border);\n  margin-left: 5px;\n  padding-left: 12px;\n}\n\n/* Tables */\n\n.odoc-table {\n  margin: 1em;\n}\n\n.odoc-table td, .odoc-table th {\n  padding-left: 0.5em;\n  padding-right: 0.5em;\n  border: 1px solid black;\n}\n\n.odoc-table th {\n  font-weight: bold;\n}\n\n/* Mobile adjustements. */\n\n@media only screen and (max-width: 110ex) {\n  body {\n    margin: 2em;\n  }\n  .odoc-toc {\n    position: static;\n    width: auto;\n    min-width: unset;\n    max-width: unset;\n    border: none;\n    padding: 0.2em 1em;\n    border-radius: 5px;\n    margin-bottom: 2em;\n  }\n}\n\n/* Print adjustements. */\n\n@media print {\n  body {\n    color: black;\n    background: white;\n  }\n  body nav:first-child {\n    visibility: hidden;\n  }\n}\n\n/* Source code. */\n\n.source_container {\n  display: flex;\n}\n\n.source_line_column {\n  padding-right: 0.5em;\n  text-align: right;\n  background: #eee8d5;\n}\n\n.source_line {\n  padding: 0 1em;\n}\n\n.source_code {\n  flex-grow: 1;\n  background: #fdf6e3;\n  padding: 0 0.3em;\n  color: #657b83;\n}\n\n/* Source directories */\n\n.odoc-directory::before {\n  content: \"\240\159\147\129\";\n  margin: 0.3em;\n  font-size: 1.3em;\n}\n\n.odoc-file::before {\n  content: \"\240\159\147\132\";\n  margin: 0.3em;\n  font-size: 1.3em;\n}\n\n.odoc-folder-list {\n  list-style: none;\n}\n\n/* Syntax highlighting (based on github-gist) */\n\n.hljs {\n  display: block;\n  background: var(--code-background);\n  padding: 0.5em;\n  color: var(--color);\n  overflow-x: auto;\n}\n\n.hljs-comment,\n.hljs-meta {\n  color: #969896;\n}\n\n.hljs-string,\n.hljs-variable,\n.hljs-template-variable,\n.hljs-strong,\n.hljs-emphasis,\n.hljs-quote {\n  color: #df5000;\n}\n\n.hljs-keyword,\n.hljs-selector-tag {\n  color: #a71d5d;\n}\n\n.hljs-type,\n.hljs-class .hljs-title {\n  color: #458;\n  font-weight: 500;\n}\n\n.hljs-literal,\n.hljs-symbol,\n.hljs-bullet,\n.hljs-attribute {\n  color: #0086b3;\n}\n\n.hljs-section,\n.hljs-name {\n  color: #63a35c;\n}\n\n.hljs-tag {\n  color: #333333;\n}\n\n.hljs-attr,\n.hljs-selector-id,\n.hljs-selector-class,\n.hljs-selector-attr,\n.hljs-selector-pseudo {\n  color: #795da3;\n}\n\n.hljs-addition {\n  color: #55a532;\n  background-color: #eaffea;\n}\n\n.hljs-deletion {\n  color: #bd2c00;\n  background-color: #ffecec;\n}\n\n.hljs-link {\n  text-decoration: underline;\n}\n\n.VAL, .TYPE, .LET, .REC, .IN, .OPEN, .NONREC, .MODULE, .METHOD, .LETOP, .INHERIT, .INCLUDE, .FUNCTOR, .EXTERNAL, .CONSTRAINT, .ASSERT, .AND, .END, .CLASS, .STRUCT, .SIG {\n  color: #859900;;\n}\n\n.WITH, .WHILE, .WHEN, .VIRTUAL, .TRY, .TO, .THEN, .PRIVATE, .OF, .NEW, .MUTABLE, .MATCH, .LAZY, .IF, .FUNCTION, .FUN, .FOR, .EXCEPTION, .ELSE, .TO, .DOWNTO, .DO, .DONE, .BEGIN, .AS {\n  color: #cb4b16;\n}\n\n.TRUE, .FALSE {\n  color: #b58900;\n}\n\n.failwith, .INT, .SEMISEMI, .LIDENT {\n  color: #2aa198;\n}\n\n.STRING, .CHAR, .UIDENT {\n  color: #b58900;\n}\n\n.DOCSTRING {\n  color: #268bd2;\n}\n\n.COMMENT {\n  color: #93a1a1;\n}\n\n/*---------------------------------------------------------------------------\n   Copyright (c) 2016 The odoc contributors\n\n   Permission to use, copy, modify, and/or distribute this software for any\n   purpose with or without fee is hereby granted, provided that the above\n   copyright notice and "
+
   let d_725c52bce5d22dff34816d0cea74cf51 = "positionData:g,children:[{type:\"elem\",elem:e},{type:\"kern\",size:h.kern},{type:\"elem\",elem:h.elem,marginLeft:V(i)},{type:\"kern\",size:n.fontMetrics().bigOpSpacing5}]},n)}var v=[m];if(s&&0!==i&&!c){var b=Ke.makeSpan([\"mspace\"],[],n);b.style.marginRight=V(i),v.unshift(b)}return Ke.makeSpan([\"mop\",\"op-limits\"],v,n)},un=[\"\\\\smallint\"],pn=function(e,t){var r,n,a,i=!1;\"supsub\"===e.type?(r=e.sup,n=e.sub,a=Ut(e.base,\"op\"),i=!0):a=Ut(e,\"op\");var o,s=t.style,h=!1;if(s.size===x.DISPLAY.size&&a.symbol&&!l.contains(un,a.name)&&(h=!0),a.symbol){var m=h?\"Size2-Regular\":\"Size1-Regular\",c=\"\";if(\"\\\\oiint\"!==a.name&&\"\\\\oiiint\"!==a.name||(c=a.name.substr(1),a.name=\"oiint\"===c?\"\\\\iint\":\"\\\\iiint\"),o=Ke.makeSymbol(a.name,m,\"math\",t,[\"mop\",\"op-symbol\",h?\"large-op\":\"small-op\"]),c.length>0){var u=o.italic,p=Ke.staticSvg(c+\"Size\"+(h?\"2\":\"1\"),t);o=Ke.makeVList({positionType:\"individualShift\",children:[{type:\"elem\",elem:o,shift:0},{type:\"elem\",elem:p,shift:h?.08:0}]},t),a.name=\"\\\\\"+c,o.classes.unshift(\"mop\"),o.italic=u}}else if(a.body){var d=ft(a.body,t,!0);1===d.length&&d[0]instanceof Z?(o=d[0]).classes[0]=\"mop\":o=Ke.makeSpan([\"mop\"],d,t)}else{for(var f=[],g=1;g<a.name.length;g++)f.push(Ke.mathsym(a.name[g],a.mode,t));o=Ke.makeSpan([\"mop\"],f,t)}var v=0,b=0;return(o instanceof Z||\"\\\\oiint\"===a.name||\"\\\\oiiint\"===a.name)&&!a.suppressBaseShift&&(v=(o.height-o.depth)/2-t.fontMetrics().axisHeight,b=o.italic),i?cn(o,r,n,t,s,b,v):(v&&(o.style.position=\"relative\",o.style.top=V(v)),o)},dn=function(e,t){var r;if(e.symbol)r=new zt(\"mo\",[Bt(e.name,e.mode)]),l.contains(un,e.name)&&r.setAttribute(\"largeop\",\"false\");else if(e.body)r=new zt(\"mo\",Nt(e.body,t));else{r=new zt(\"mi\",[new At(e.name.slice(1))]);var n=new zt(\"mo\",[Bt(\"\\u2061\",\"text\")]);r=e.parentIsSupSub?new zt(\"mrow\",[r,n]):Mt([r,n])}return r},fn={\"\\u220f\":\"\\\\prod\",\"\\u2210\":\"\\\\coprod\",\"\\u2211\":\"\\\\sum\",\"\\u22c0\":\"\\\\bigwedge\",\"\\u22c1\":\"\\\\bigvee\",\"\\u22c2\":\"\\\\bigcap\",\"\\u22c3\":\"\\\\bigcup\",\"\\u2a00\":\"\\\\bigodot\",\"\\u2a01\":\"\\\\bigoplus\",\"\\u2a02\":\"\\\\bigotimes\",\"\\u2a04\":\"\\\\biguplus\",\"\\u2a06\":\"\\\\bigsqcup\"};ot({type:\"op\",names:[\"\\\\coprod\",\"\\\\bigvee\",\"\\\\bigwedge\",\"\\\\biguplus\",\"\\\\bigcap\",\"\\\\bigcup\",\"\\\\intop\",\"\\\\prod\",\"\\\\sum\",\"\\\\bigotimes\",\"\\\\bigoplus\",\"\\\\bigodot\",\"\\\\bigsqcup\",\"\\\\smallint\",\"\\u220f\",\"\\u2210\",\"\\u2211\",\"\\u22c0\",\"\\u22c1\",\"\\u22c2\",\"\\u22c3\",\"\\u2a00\",\"\\u2a01\",\"\\u2a02\",\"\\u2a04\",\"\\u2a06\"],props:{numArgs:0},handler:function(e,t){var r=e.parser,n=e.funcName;return 1===n.length&&(n=fn[n]),{type:\"op\",mode:r.mode,limits:!0,parentIsSupSub:!1,symbol:!0,name:n}},htmlBuilder:pn,mathmlBuilder:dn}),ot({type:\"op\",names:[\"\\\\mathop\"],props:{numArgs:1,primitive:!0},handler:function(e,t){var r=e.parser,n=t[0];return{type:\"op\",mode:r.mode,limits:!1,parentIsSupSub:!1,symbol:!1,body:ht(n)}},htmlBuilder:pn,mathmlBuilder:dn});var gn={\"\\u222b\":\"\\\\int\",\"\\u222c\":\"\\\\iint\",\"\\u222d\":\"\\\\iiint\",\"\\u222e\":\"\\\\oint\",\"\\u222f\":\"\\\\oiint\",\"\\u2230\":\"\\\\oiiint\"};ot({type:\"op\",names:[\"\\\\arcsin\",\"\\\\arccos\",\"\\\\arctan\",\"\\\\arctg\",\"\\\\arcctg\",\"\\\\arg\",\"\\\\ch\",\"\\\\cos\",\"\\\\cosec\",\"\\\\cosh\",\"\\\\cot\",\"\\\\cotg\",\"\\\\coth\",\"\\\\csc\",\"\\\\ctg\",\"\\\\cth\",\"\\\\deg\",\"\\\\dim\",\"\\\\exp\",\"\\\\hom\",\"\\\\ker\",\"\\\\lg\",\"\\\\ln\",\"\\\\log\",\"\\\\sec\",\"\\\\sin\",\"\\\\sinh\",\"\\\\sh\",\"\\\\tan\",\"\\\\tanh\",\"\\\\tg\",\"\\\\th\"],props:{numArgs:0},handler:function(e){var t=e.parser,r=e.funcName;return{type:\"op\",mode:t.mode,limits:!1,parentIsSupSub:!1,symbol:!1,name:r}},htmlBuilder:pn,mathmlBuilder:dn}),ot({type:\"op\",names:[\"\\\\det\",\"\\\\gcd\",\"\\\\inf\",\"\\\\lim\",\"\\\\max\",\"\\\\min\",\"\\\\Pr\",\"\\\\sup\"],props:{numArgs:0},handler:function(e){var t=e.parser,r=e.funcName;return{type:\"op\",mode:t.mode,limits:!0,parentIsSupSub:!1,symbol:!1,name:r}},htmlBuilder:pn,mathmlBuilder:dn}),ot({type:\"op\",names:[\"\\\\int\",\"\\\\iint\",\"\\\\iiint\",\"\\\\oint\",\"\\\\oiint\",\"\\\\oiiint\",\"\\u222b\",\"\\u222c\",\"\\u222d\",\"\\u222e\",\"\\u222f\",\"\\u2230\"],props:{numArgs:0},handler:function(e){var t=e.parser,r=e.funcName;return 1===r.length&&(r=gn[r]),{type:\"op\",mode:t.mode,limits:!1,parentIsSupSub:!1,symbol:!0,name:r}},htmlBuilder:pn,mathmlBuilder:dn});var vn=function(e,t){var r,n,a,i,o=!1;if(\"supsub\"===e.type?(r=e.sup,n=e.sub,a=Ut(e.base,\"operatorname\"),o=!0):a=Ut(e,\"operatorname\"),a.body.length>0){for("
 
   let d_75490a0d375710a28ff64d8f55ab1d68 = "wOF2\000\001\000\000\000\000\027\000\000\014\000\000\000\0000l\000\000\026\173\000\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\006`\000D\b,\t\156\012\017\b\n\1794\169\r\0016\002$\003|\011@\000\004 \005\137\030\007h\012\129'\027\019*EF\133\141\003 \002g\150\224\255K\1306F\b\230\031\182U\021(xF\163\017\021\182\149\128pX\219\2267Uv\016\254\175\2278\0146\026\165\222=\167#+\183\026\209|_\249\002%\172\225\208z\156\2514\159\137(\176\163\020#$\153\029\158\182\249\239\146\163\143#\1420\142(\t\001\019cD\170XX=\172\218\204\197\223\156\155\155\203\252\181,\127\165?+\247\191:S\255u\147V\201\178\003h\199>\002\150\173\002\194z\183&\175\219\001O\005\156\000Q\177\219\169<\255\253\145\158\255\238O01\142f\162Kk\rH\177S\225\130Ud[\1416\241\190\251\230\222~\236\238\171\011\028\131\191S\166\175\198T\1580\153wn\198n2\129\143P\130\020\1287\217\003Ux>u%\023U\194\n|\229\135w\236\000\0298\164\165C\144\130\210\173o\139\250\138\218]\245\228c\011\221\252\155\183\144\0291\173\136\208\186i\162\243'\161\148n\201\242\167\248\150\137\211O\244\246\031\136vXF\160\197\217\173\187\175A\016,\r\136\201\217\249\255\159\235\211\222\251\146\161\020\000\151\\\209\1630\021\186\198\188\185\153L\031d\230L2\255w\003K\201\018e\242\255~Hq\025T\193\163\220\179\1704\179H\234Wn{<\t]\237+d\157_a\203B\218\202>\134\170'\128\201\167\134\167\237\246\187WM\164k\185J\144!\152\249\022\179\227\171w}\001\028\186\238\131\001\240\205u'\000\219z\161o\021\003\006\143\027\t\207\159\001\224\007\210\183\223\249\022\021\151\161N\224\1978\1380\157\1711Q'\025`g+b\149\192w\0006\215\011\237II\167\161\135\219P\014I0\r[\175lt\244\2185\r\243\229\250\175\031\2335.\155z\131\187\160\235\029\245`\255P\0128\191\238\n/\172\002\168\241\253 \178z\005\0047\171\224w\191<\153\007\152^\226X\154\154g`O\215\132\016\146\024\233\145\177\022\208\000\bh\175\005\144\004\162+\128\000S\199\0050\212\170-@ \245)\178yk\194u\017Sbt\025\222\236\186\172\239\018\152{'\002\207\128\217M5\232\245I\011w:\140\014\245\228\129\005f\183\021lM\158>\016`\170k\197i\163\027\157\002*\252qhe\169\019\024\208\030$\144\210/|\022d\142\225T\141\212\194\162\002\154\127\181\166\180\196\254\168\015^\188\005\241\176\243\219\015\245\154\166^\169\184\214\164w\247\201\213\172\202}\t\146U\146jL\213\209\242\024s(\135\003,fd,\205\150\244\006\028\025\r\197\216(\142\134eCv\016C\0249\003\176\195\227\b\016\247\128\146\007iea*K\201\167\156\165+RF\150\231\185\194di\bu\n@\017\002\016\b\223!2\170\011\005\024\164/\160\158j\129\197-\015\203\028\1329cm\000\170\0058\238|\129X\145Yc'FT\182k\202\160\179z\156\223\t\216\200\186\166Ni\152\255\171\147\145\029S\014\154\183}\2202i'x\r6\b\222;\191(C\143\147\210\177\nX\128\205N\011`\190\129\200\178\205\169\000\142\167%\224\241\024\232;\1285Z#6$\235\130\128\163+T\150\138\167\020o\r\166\221\216;\157\140\131\150\189,\129\190{m+\b\184\235W\148\203\243v~(\020\016\000\245(\253F\219\164F\221\007*f\214\194\028\224E.\000\241\160\219\011\181+\252c<t\211\b6z\011\002*,s\202_\020\164\184Nm\141\218\240\218\022\b\145\225N\1613\158\020\144Xs\"\b\185rP\253e\133\185\000\169\197\184&e\003\017\023ltN)W\168$\026mC\196(M\187\030\220\tzJ\n\171{>\163?\189\240\020\254DO\012\016/\218\246\171\187O\158\177\171!\158Y\130\012\168\238\190\160\186<Ps\136\162\247r\192\238\178\240\025\201\137@\219* \190\229'\028\243\160\238\154-\018>!GV\199\155:\215\216\001\\\231\246k6 \228\0162\215\205\r\176\182)\\\1585\003pC{@\004,i\161\148^\174\153\020\019\025\\\246<\1489\233#0\007\223\128\170\147x)\223\157\020\209\196\141\t\231\028\017 \185d\160\150%\179\193\214\206\193\147P C\006\210N\001\2213\b\228\012\006\005C@\201PP1\012\146\024\014\201\140\005)\140\128T\198\158g\129\2020\016\188\174\238y\149\018\232chx\219\214jT\145\153\191/\180U\012\230\223ac0\193:\224.\002j\231O\164\214\131\137jdP\131\138ZT\212\161\162\030\021\r\168hDE\019*\154Q1\ru\161\029RU.\164\231\"\242*\221Tt\151\219\020\170\216[\183\227@H\196\250\197\140\n\156\016\025\138\168\169\1669\157\240\155n\169\012\t\224j<\166Y0]\026\239h8G\025K[}\2556\128u3p\218t\219\133\153\144O\000\230faB\237\164\196\142\128\"\167\141\239\167@v\0066\133\2227\157\203\153i\011\242a\201\134T2\132\017\000\002\244\011*\200Ay\167*\200\189&\001\226hl\162\027\025\022\2173)1\002h\135f\217r\179ehlE\018\127d\150\239DsmnJ[7_\215\222<\000d\208\151\135\250\2116?u\230\137\031.;\199\141\221D\170&7\189D\254\144\148~;\224F\211)\018\218W\203D\239\141?EuVM\183\"\207\238\007\183pWr(\141\2141\208A\164\247#0\bZz\141o\167>(c\173`L\245\150\160LFR\241}\131\174aR\153\026\148u\144\230\140\194\225\224\155\171\203a\180\131F\185U\170\164\006Td\229\2111O`\222#\208\156\012s\137t\206B}OL\017\174v\001%R\204a,\171@\1719O\165\176\011\199N\0122\005'1\219Kl\236\162\026\132s\227)\213\190\148J\173y\253II~-\212\208\195]\220n\2497L\131\205\1416\189#\154\178\218o{>l\017\156W~\188/S\199wM\174\003/4Ndr~j\154~\203\236\004/U(\179#mvB/\246\189z\199l\237\220\239c\147\029?w\000\228E\224l\016\228G\195\236\212j\135\216\228^\211\003\206\018\199$\132\186@\214\166n\022`U\130g\014\003\170\212uU*)u.N>\140\204\233\185\187vK\215\246\175b\216\204\004\141\214\217\199+\1573\182m\134m\200\023\"\243@^\135\028\025\021\249>l\245\142@\173\135\005\022\185\210\254\247[0\232\226\134]\205\030\189\146\226e%\200\000z\245\200Y\146\024p\127B\233\137\128\172\175R\202\160\2092$\210|\169\178=\196\183\030\185%]D\133\001\170\005\161\198P\186->f\144\002\211\130\208b\244\218\167$m@\199\000\220\027 \244\012\148o\207`\001\131\133\012\0221T\028\027\015K\232\006R\011\194\140\161r[\252\172 \005\165\005a\197\208u~X\163\193\026-\214\232\176\198\000k\012\177\198\bk\140\177k'\153\022\147z\170\245`\205\156\161\160\230\232\219'\228\139\023\025\182\176,\193X\149\000\235\2174\222qc\014n\205qw\151\144\195\030\129\204<\160`\030\145\195i6\217/\158M\227\1974^M\227\2051\132{\t\208\151 \031\185\018|\154\193\151\025|\155\193\143\163\224[\002\252JX\248o\163\185\191p3Wq\213\019\n\011\023\190\208\170U\234\134\006\191\229*\209\245\128\232\206\166\191\180\007\216\000\004\234k\1326V\170\234\018\199`\000\226\030\224\188\216TQ\015\158\0040\005;;g%h'\176f}\245\003\004\232\012\172:7\014\170\186\178~8Z\172\245F\018u\197Nz\233p\139\175&\171m\180r\144\139q\209S\238\201\r\216\197\223\000w\1903'#~$\137\175J#=b\205\240\244\135M\011\146X\128\252ss#xK\236\r[\174\215\145\250\190X\170\198X\232\199\196\132\162z8;\208#\146\128\239\193\186k=\209G\b\017\188\192\158\145L\150\1733d|\179\223fgyd\188\239h\1610\014v\181\016\160h\167O~#\004\224c\188+\016\224\197g\1743M\012\240\028\191\\*\161E\223\204\170\017 l\164\145\207\179f\134\017\160\137\003\222;A\136\1799|h\2037\236\207\022\1775D\143\020\237\1713\225\240l\184y\024\219\177\"\196\221\"4\245@B\128\158\247|pf@uMW\148\252/\224\181`\200\154L\001\161<yD\134)J\225\023\236\198+\194-\029\197\155\144U\215R\208\183\1832\147\tl\161(\212\174\001\166v\n\2314\128\172\229\168O\203?\171\213\241\203V,\208\186[\198\233#\005\131\027\168?\141\190\154\202\212\237\155\017\133\024O\249R\180s\0065\241$\156R\221\179\003\180\227\214\144\167A\029\205mr\206\160\134\248\1724\001V\031]g\152\183 <j\186\145Lr+\184|h\164\2046\170\002?\242\212\214bl\142\237M\184\000\203+]\129\195M\151c\137\162I\242<\nQ\186V\248\185\158\020\231\025}\177\201:\234!\190#\189\135\138T\186#@^\193`O\167\154\251\031\149,\170C[\208\172\222\206\244-\234G\180x2M$7ei\000\176\163k\197\211\b\238_X\240F\157\141\231\000\181\245\217\234\130\149}\158\165\234\210\184\128\160<\162\172\184\137Q\131\184\145\166\132\226<\192\159:\182\t\170G\003{+>\022Gj\011?I\026>\1440:\183J$\229\028\142g\024\023\215\2449\161\133\237J\190\211G\237\232\178\234n\223\029\199\210\174\166\174Gd M\151\135QDO?\180\165\191HF\205>Q\028\211\017\248\182\250\180<j\023\167\137\230\175\246q\152\199\020m\211,\153s\180\b\158\176\182\168L\000V\188\029B;*\145\198\195\157k\150T\143\148\1530yK-3;\149V8\167p\027\145\025v\238\251\169\198\147e!\175\143\198'Z\157\233KSt\129\243\213\218K\1709\163%\021\185;`\029B6\135kC<P\188(\146F\206\202V\218\200\135\n\215\223\004w\218\170zC\248T\229\248\150b[\030\185y\141\195\195\016\1733\220[\212\n;k\130s\016\027\212\004|$\141L\185i0\231\228S\252\179\016\180\025\249\192\153\0117\162\254\023\137\198=N\237\157\233\247gf\027\211L\218J\172\t0\017\180P?i6k\027\133\176p\223+\188g\250xp\239;\186\159C\161\220\"\020\005\127\212\031\244\145/\1536\002\014\192\004\231\254*\169\190\192T\024BE\163o\164/4\160\144\136\166 Txl\200\165\003\023c\227p\029\205!\147<,A\255i\187-\253\163\227^Aj\155\000&\006!0\186_\028\209\205n\196\151\003I\226\229\249\197f-\201\020\190\0072\237\2406\220\252\025\241\255[R<\238\181\159\185\225\129\171\214M\177\208\231\150\199\213\0309\199\002\249\179\202\214\194\187Yg\1986\210\012\160U{\031\250\176\228i\005\232\1701y{n\129\002IV\158\159\026*\160\216\231\220\195vEqCg}=\186\240\138\218\149Z\\?U\182\233\129JJ\251OUb\022\b\023(c\b\131\245i\179B;\234\169C\015\160\014i\195\154\017\139-\218a\162\205\226\138i\150[A\2356\237\224\022)\231\146\218[WJ\135\031+L\180P\011\220\169\026\161\026\004\168\020\139+\156Hm\161i15S\205\150\176\184\225\138P\211j8\005(\156\241\138\198\245X\b\214L\248\255i!\198\223\140`\177\182\170\023Z\016f\142\201{K\191p\012#\182:5y\20342*\241q\235\250@\r\245\182\140D\241Fz\193E\233\221\180E\189\178\154o\005\206\162\176\005^B\020Bh\170E\031B5r\225?0\023\138\170\251N\251\191U\1331\187\025\184;\021:Q\158\161|QM\235g\206\157\231\207\171\158\183\241\229Z\212\019>k`;\217(\220\1461\006\170\236\167s\128\170Ei\226\233RQf\007_\229\143:&\249D\2386\220\183\182\145\007q\134\228{-V\031\225\20477\210\226\003\016j\000\177\127\222p\199(\201\134\193\186G\151\190\217hn\137e\244\131\186\174Z\224\207\197\142\139\243~\207\141L\195\012\201\227Ox\172\180=\185\156\175\003N\179h\170\1800\150\193\168\255\017\187\162\198(\021\225\1837\1968?\137\243O\172\222\189\196\233\020\012\146\193\180\b\190\1470\192\251J`\2133x\162~\247\190\160H\238\183%\241\rT\193\209\138\243 Y\159x\nw+\b]\175\016\171\243\221(\170\145\003<\191\173hT4x\193\005\175\bU\011C,hF\005W\169v\165\203:\136\208y\225E\007\164\000\2231.[p\135\179\185\191\162\001\029\246w\146\231\199\028\226\r\250FE\136\"\239\r\241\205\158gAk\159\197\179\031^(\176\200^z\018}\173n/B\127q\170?h\226\218,\030\195\209\226\011\163\156\\f\235\149z?\172\021\182\185nO'_#g\195\243\203\208\194_#\019\233qUnJ\191\227\031\221K\255*~\242\153\137,z\152\250^\233\132\204\207\147p\186\022\\`\187\195\244\181M\185\003|\153\017\134\\\003r\140<\2239\179\251\174\201W\"\201<N\238\1907\031\131\143\"\188y*iF\226\021\132\201\178;\006\217\232\170;f\184\127\176U\207>\028LI\006\238\151w\210\137\170\221\187@\238R\243\212]u\180\141V\1494b\156fd\003\129\160\194\175*w\018\249\015\208T*'Lfti\250\027W\011~\018\143\190\127ca\150:\184\230\212\250x \230\142&\187o\239\173\154\227\143\202\138\148\207\202`D\024\188\215\207\253$wv4\216\023*'\246\179d\1480t\255\235\156\181i\242\167T\234O\202Nf\182/\168FT\003\174:\251\200\128/\137\"n\181\197\020=\198s\178\243F\164i\131\146\166\146\254\187c>0+\195M\247\168\196\\\195\246}m\005\029D;\2137\177n0E+\152\140vo{\224\027\137sw\202\231N\1878\238\215\022]\146\249\024\165L\130\207\220\212+\021\234\140\137\194p\164V\184B,\030\240\230~\225-D!|\224s.n\2167\241\135s}\253\135\188w8lC\156\018U\021d}\2387\164\210\020\162\248\160\186\"\183\222\186\146\005\005\128R\017\006\176K\244V\185\181\"\187e$zn\232M\238\174\006\243\198+\136\b\003\240(\139\254\178\253\131\2450v\207Dq\137K^w\031\161\185G%\"\159\205\216\025+\229\028\213\216\030_\158\210 \242(\250'\170\\\1994\190\189\249\222\251\159\159\247\006\240\n\002\200=\209\157&>=\251\199d%W.\192.\163\146\223\014\024\221\027\166\140IAm\169,MF\2259\235\224C\159\190\020C\022\176\213\b\219V\147\2386\023\189\243=~\136K\149\223}\1925\156\243}\127(\203K\202^*\150\028&r\202\178\212X\133\195/\234\006\231u\152\248YSc\252V\221\130\231\208{(\205y\138\224.\176{v\151\194\204\223\255\176\135\218x\184x\194g\251\148\218\176\023c\181[\234\017\011U\166\239\151\190"
@@ -226,8 +228,6 @@ module Internal = struct
 
   let d_bc09ffc76f5ede808ad7b59b5a5cead6 = "\197_\155/\208\137M\156t\007\2026\000\192JQ\152\138c\170G\181-\197\030\153\023\253\181\224\254\161\221'\161\177\243\021\178\159Es\137n\\\251\196\191\186:9\003\227\128!s\180\131i\001\201\017\188\239\021\245\216AS\210G\022\145\134\027+L\223\184Di\203\n\241\218\0184Cb\226\169\233\163\255o\248A\t\017\255\011'\250\245e}\028\139^LT\184\147\230\172~wcy~M\160\161\189\170}\248x\007s\131/\143\180Ui\202\185y\249\207\164\250\172\250\207\151\170\1555\237\174\204!\183\030\217\r\219\222O\163\153n\"\194\173;\195J\243\245\169\254\161\222\\\252:\249\217\205M\134\144\138^\252^\011\1956\176Q\148 \005\168*\132d\1655\138\200r@\007Ll`\029Q\007Y\197\172x\023\207\020\1538\241\131A\1873\171\143\136c9\218\006\252\002\019\198\185\211:l\218J|&*\b\182\249T\217\146\202\166\245\015,\209\230\205\140\141hHDDns\"+}\130-s:\004\178\000P\171|\144Td\165\179\202bT\214\145(\023g\234\182\156X\186\148\150\136C\1599\152\230\140\182\185\216!\012\166\\x@\200+R\238K\210\240j\178\135\180\255\215\003O\027\132\142?\237u\235M\227\166\155\242c\208\143%\252\011\148=\227\213\021\175\n\026M\216\203\255\234\\sG(\254\131!\190|\171\156\202\176%\149/k\173\232\248`\157\194\240\165\150\234\163\172r\210\232\004\216\216j\151i\205\188\031U\252\199\211\251*6\219<\142\233\215\0262>L\209\\Q\232p\245b))&\2320S\011\193\025\153\r\250w\144n\203\238\248\195\155\006=\000c\140O\159\254}\197{\162\194^9E\197\022\030{\247\218\2165\189\221b\151Z\247\152\183CpFF\028\201,\129\216\169\228,\186N\238\029\031\250\b\151\b\011\127\200\183^\252\181r~\186\1563\019\193\198\211\129-\211\150\212\247S0\137\165{m\187\"\232\204\016\2278Ri\179\193\249\171\188*\005\207\164u\1648\241\195\011b\018\196)\138\138&\148\189\127\255\193\247\204y=\005\220w\020\031\025f\173\153\171u6\186N\183,\213\191i\239\023\201e>O\145\137\014\232\163\179R7;\229\250\133\213\202n\1460\239L\194$\186\200\190Qmu\017q\242\206\236\133\\l\158\n{\242\"^\187\220'\208$\182Q3\255fs\133\135\227\029|F\155\021\004\138|\193\210R\183ct\209\179\209\218\183\222D6x\133\245\223\206\174$\017\0305\022|\153\244\138A\175\197\233j\227\240\164\142\151\232P\149\254^\145a\237\173+^\t\233^gj\178\242\238\139J'E\r\213|V\211\192\193\027\145\208\217Uw:\237V\181E\135k\200\0302\181\164a\197\173\148\184\231A\157=\231JV\166\220\153.Z\156\169\243\188\129\1318\197\194\208\146\208\238\188v\248GC\233\229\1569\217I\169\189\164\194\0120C{wj\236\188/\029A\239h\148a\223\145aOY\210m\214\189\133\173\224\129\163\234\154\181\137\128}\197\"T\168\023\204\253O\254)w\153\018\2504\182\159\245\028\151\002\151\203\130\191|\228\128\129X\028\187k\219/\195\203\247\173\232@H\\L\198\209\005\153W\142\r\206;\158\187j\146l+\230M\219\238\1787\200E]~\148\145\1886\255\r\157d\228\224\247\247\187)\233\215%e\023\028b2\142\207O\169\028^\191t\177\240{\017\175\244\149q\164Y\174$0\251\r\\\248\006:-j\244\145_]\185\130\012\173 \021\233\247\031;\142#\241\153\234E,*\169\255\018rmv\n5G?\196\145f\213\029\186\212\176n\171\142}\236\186*\181Z}c\249\004\202\030\227\012\207\019\015\191j}\211\200\012\031\156\142\144\197\025\188<izyc\204\145\154\245\232U\163:M3\190\139x\011\207\021\170\1411\190\172\228\193\012\203\232\185\017=\142c$\128i\160*r9M\187\199\0300\235?\163D\24038\"\189\174(\153\130\186\173p:\140\166\250eW%\186m\191\222&\210\157\024\170s6\252n\206\193u\239\129lZ\212\021\196\017\166\205$\252\207\240u\186\021\247\160\170\130$\211\168i,\169$\223\022?\166V},\196\240\178\005\028\255\229;\030\155a\173~\029\140\155M\249?\199E\129G\173\237\199\251f\226\195\015Ijcc2\145\189\198\176F\183rkQ\127\209\000\155'PO\136,\001/\015\190/K\157\143\187=\195\176\000$\221E\129\146\019\166-\196\165\156\226\138\193u\163\031v\148\148gV\139\023ij[F!wYm\188\225\232_\021Um\000d[\178C\2438\\\184\249\232\231\131Yc\158\218;\163\197\237\136\160H\000\024s \254\170\251L\021z\002\142\016\193\192'\1509\134nq\179\208\152}\181\178\249\141\255}\rM\025_\127Gn> \135\151/\207\235\250#\225\202^\151> _\195(\210'\001\nD\145y\230\155Q\1433\252\240[\234M\158j\004\164\167SFnf\006\160\230S\205\133\255\233\179w\203\016;\011\145\176i\164\183\188Q8\171\189\216\255\012\246\229\163J\172bn_ir\216\170|\152\215\020\233\214\250\000r\251\171\156p\239\015\\\131W\206\142>e\006\1392\146\210\238\154\254\228\187>e\200lL6d\220\016?\247R7Fy4]\247\221\255R\183\220\2242\232\127\215R1\252\233\143/\232\011\030\232\213R\145\160\204\233\031\016\192A\128\208{E\158\156p\241)k\201\237f\169L\1308\129+@dt\217B\1391\185r\247\1915\011\223\142\144\193\179*\169A\002\167\221\018-\206\248!%\131\146\181\210Q\248\194F\229\247Z\146\173\224M\r\231q M\185\249\rK\225\r\137\163T\182\135L\169\2021\172\209.\005pU\196\190l\029U\215$\218\171\222P5k\209\129\168I\164I\254e\164~\001\136\0299#\192c\011Qi\166N\192+\005\226\142\146\234\029\209\156|\251\167K\161p8\\\021\189\133hNZ\158\179\127\200\170\172\174K5m%=6e\r\188\248\206\177:\027\n\138#9\149K\238\196\222\021\241\150\148\144\170\166s\187@\244\225\006\217t>\225\005\251\127\0120\002\015D\1776\158\206\\B\170~'j\157\166q\243\014\212\003\181*\239\249\250]S\227\147K\193wv.\160\156g\015A\228\190\199\012\154eud\247\214\158\181\155\222\235(\171r\214\n=\132\147Ro\2450\007\144\167\031\130N\152mX\006\\\181\025\142\166;4r\133\180Sa\180J\167Xp\"\015\214\175\254\247;8\247i\176\226\23772\018\127\r\154\181\201T\182\159,\011\r\172dO\235R\186\026\145\210\130\143\182)\155\235\235\202\220G\136\207\152\194`\135\223p\023U\030_\186f\251\r\234z\149\190\0302\198/\182\217\146\237\204\251\216\132\002\134\194\021\176Q\253\164%\163\213*;\229\151\184\002\135|Q\183\153\227U\210E<\023\249\222\018r\007\185\250\181\011\218\146\159\212$\215}\171\158\2036Z\171]tQ\1676\174\012\138k\012\n\187\234\031\173\200\211\248f\202\021\028\232\194\160Ew\156\021q\135\229\201>[\150R\225\161\022\255\152J3\200a\160\215\192\223\195Lf\002R\142G\207\240\136G\174\012\140\253o\239\221\153\142Q\244F\169\250\149\143\003\227\156\190\203m\002\n\215b/a\128\001{:\157(\2170\237\192\177!\002\217\191{da\025\254c\152\188'V\1311\13883\005\141\222\029\227K2q\228\156\204-\147o\205\r\023\232v-\166\182\160\216\202\143\236\212\196m\166\151p\2278\253\029MMVxw\001d\137\207\021u\246n`\147\240MpvI(/\2456\179\152\022aI\002\219\019I\142j\255w\1331\017#\132\021\255\012\244\2267\026/\135\246\015^G\141\007\1280\003\127?\129\140\158Ct\194\220\188<o\129\031\196\190\250]\128\165V\022\017\155\151\002\242\208\205\170\175\029\030\248\253\247?4\235\1951S-o\223\252\007\027\134J\022\219\152m\025\168\224\025\216\172\019)\019V)\223\003\212=\019x\246K>\138\0112[\030\018\227\b\021\169\163\204\012|\253\148\133\169X\228\252\223\245?\000\189\255\195\175\016\250d\131\239\222\169/\159\027\232l\030\168\174\127\161{\2319g\185\187]\158\1965\132\195mm\201\167>\216\180\007V\169\193\192@FI\\\174\016\"2oZ<=\149E\000e\150\203F\004\223_l\162?.\167\150N\224\230\128\203\227!Q\235\220Z\176?\253\222T\136\241\250H:\219\194\r(\165\139\174jy!\172\001\n\132\133\204\136\003\145\006\129F]u%r2\210\029qi\222\164\224[\252[\026\192\203?\024\188x8\005\2271x7\140wu\206*\252\151;\225\196\150E(\128JhF\017\202\nw\017\164)\154\219#\017\160\191\188\242\024\212\179\236\134\183Q\130\2463\174\190\192>\182\248\026\020\132lwq\012\203\211\139!x\243(\130L@,C\229\002hS\205T\211\144\217\152@`T\129xG7A~_\226\2313\t\020\209\223\nC\152\029\018\210\228\0188\007\b1 \145.d\247\185\023\174\024\155\195\239\197\154D\248\026\239\210\244\219``6\253/\138\235>\021\020<\176X\248\231\139\\6\164\t* \216^\005\004\222\145\139\190\178\006|\173cG\028\192\253\000E)\012+\191\128AgI\144\205\025\219W\143\156X8\027&W\152 \004\216vm\217=>\031ZX\142\188\240\253\227\t}cjT\238\192\209\166)\251\146\154$\210\132a\183\230\193iz\\\173\232\007\250\193\203\210\174\221US\225}k\"9\016\178\176\017\159\t\159=\219F/\2382\023/q\168H7\172R\212{\211\149\246PAK\140\226\132\000$\211\132\163bU\159\200#\206\144\246<\234\146\201\151*U\152&\162s\rM\167\028\174\176 \196T4S\149\139\164\195\n\221l:\012\191\178\144\216\1871\249\234e\199\228\254\132\186\029p\148X\251\152p\018\025*\140\002D\252G\167\202\228{_\207\247\189h\246\248\0075/\0170\005\1791x\193\007\170m{E\017~\014\208\2053\220\239{\254\007c\230\219\189\205\000 \210w\210+\011\159\175\231)LZupQ\151h\255\253w\232\215\001\164\187\171\141\182\133\207\022\164\167\252%\186\156\161\250\011T;!<\030g\141\193\179\162\145\167\224\185\199q\000@|\210\196/\014\007\142\146\160\158\\\148\146\246\176rV\197Y\159\213 \174\208\212\017\170\244?.\211Ak\249\224\006\230\242\003\247#\150n\170\220q\028\144\b\232\031H^\153\252\240M\172u\228'\127J<\2171\186:]\247\240\213\244\014\175\170\011\159\184\223e\017\168\140\192Vb\017j\184\168\190\203w\191m\229\212\201!q\1320J:V6\144\225L5\137\017u\021]\191}]R\177l)\006hs\218\154\157\213\183\024)R\222\135\161\193;HS,\026\019\148\242\225\170M\142\198\154\148\214\170\018_E\177\252\228\248#\139\218\158\211\tFL\217\018\223z\214\227\143\246\t$\2486\136\231\240^M\151\173\0000\001\200\180\142\228\208b\157\134\220bt\195\180\178\212az\246Y\251'\231?Wg\007\227\149\029)_l\217\190J\176\226\154\185RC\001\231\011\148\226\028\167\251\b\255\030\168\014\219s\222\144^'\249\020@\247\029\022\249H\155\223\132o\181\187\148\238\022&\235\147\200;3WJ\252\153\138\"'\189\216'u\213\2077m1\012\135_1H\022JdK^\000\224W!E\147\204P|\237\166\135$\183Rb\020\249\228\207\215\221\157\" \017\n\180K`0\215\212o@\004\023\b\201!\211r\235\018\179\220[:\162P\194\137\195\229y\222\156lE\230H\198:\146\151\174\018k%WR\163RV\150\127\222\017\250\201\014\233\230gt\n\002\210\149v&\203Ba\198\152%\011*\153eyD\139z\155\235+JT\000}\0273\188.\215\146>Ma \201B\200\199\200\133\180\172\128e\002\242\t|XR\012\192\023A\171B\b\201Z\169\156%\150K\211\229\016+\210ph\208\151g\215\180\021\241\131\206V\150\184\147i\b\1291\129B\135\221>CI\176\225\142\213RF\144\151\139\224`]\165]\028\028\236)H\025\019\171S@\131\2066\213\006\01150\178\138\\\029I\1764\131\132\185\194?n\172\251X\159BN\021\249,u\221\250\198\t\165*\139}\198\166\148x0\174\218K\2284\212\248S\197\190ZK\019E\n\n\217o\172s\224<\201\022J\182\243\178\022\241\169|\234:)Z7\1482\139\000 \244\209\249Y*\203ec\017t\145\172i\n\214\250R\153`\129\211\196\248*\173pi\158\213&\027\164\169\"\003\193N\202\204\016A\203\229\136\172F\204b\t@\148$A\029#\004Vc8E`\216\254<\163\144\142\011\224\146\194H\135\164\146Tu\018\184.\007)\217\165\146\029\128\147,\005)\177\000\014(i\"\018P\234\142\155\213\156\185\194\2542g2%\139Hh\132\222NWcm\200\197\186\207\006J\243\179\236\210f\145\197\184\005\215,,\202\216^G\172\210+\134\234x\130'\173\216d\017@\146\136o\006\014A0\172\249\017\241\206\208se\024\146\210R+D\128\226\137^\183E)A\016\161\012f\166\200aY\001\201%\004\183\003\182\183v\213\242y^\145\\-\031\151\207\011\022\241\007\011`\158\016\001\246\166\017L-\011\002\016\181e\143\214\249\163\189\220)/\254#\228\200\215\156\187\175}9\019c\181\174\193\209^\167\129 \002\130!\200Mq\149Z\026j\237\255\017\180\024\208Jtv\019\127\227\234\144\172\001r\150\r\0017\243\132\161\019u\1774\203L8\195\134J\230\173\220\206n\200P\153\225Y\192\219\157`\018\196\156T\240\211\209\023lp\021\238\194\153x.^\137\199p/\159W\181\187\t\170/C<q\251\252\138\"\167\200\247\"\183zC\158G\200u\0079\197\161[\003\027\150\155\017\156J\161\218\002(\199\165\228v\152\162*\205\254\128\2222\192\243\012\252^\190\139*/r\127\128>\147\249_\171\255\162\216\177\195\023\156M}\220Tnk~\206L\2086Z\0307;\023\153\175\207\177\208y!\250\205\131\004@\131C8L\175\145\226\012\130\160\166\186\b\155\025\153\217`<9;G\220\193\183S\157j\154T\001\189\024\196\251\178\151(\204\151\000\154\139\252\015\134\129<\158\252`\166\189K)\196\232\230\193\192LG\227\200\nH\211}\143\003\238\228\190T\2075'\202 \250<\158\bb\019\165\195\206\175-\203\187\232*r\0013)\023A6\030\247\b\005\238K~E.\249k\164o!\189\247\193.V$xO\255\1834n\158\023\215\018\134n\136^\224c{\128\028@Y\140\190\007\n\133\020P\2181\t\210/\018H\239)\180\196\246\2146\132\248\128f\217\n`\029\216\n&\241\232V\b\159\255\173P\230\160[a|\177\205\1437n%m}\160\255\196\202d\247\139\2524\186\128I\192\225\2170\187^g\143\164\139\227J\021\200\184Q\167\021\026\0050,\007\170*\138\170\136\025J\229\244\210\231\149\213\225\187&\194\127\184S6\206\167\225 '\176\177"
 
-  let d_bcdcf563a38bb540aacbb0c6c928e02e = "HANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR\n   ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES\n   WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN\n   ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF\n   OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.\n  ---------------------------------------------------------------------------*/\n"
-
   let d_be9d59550018d5a14883040df88dd06e = "\151\229\161/\228\151\211-O\128\176\195D\128E\133\227\190?\002\028\167\1942\186\201\143\168n\201\174\214P&\199\016\156}\192w\015\0125m\128\127VE\028\198\180\227\140\228\255\r\227T\005R\241\185\140gyFs\028\225\236\003)Y\150\146\198\233\214\003$s\185d.\157\019GS\005c(\147A\255\219\135\160\167\196\204\168\003\153\012\221\026\235R<WJ\24757)N\015z\187$D\128\151\020E\239\217\220\224=\153\135 \198J^\244\212\147>b\152\166a\166\204CJ\028Ee \177l*\219-\178\201\189\159-\239\161\153\221\020\140\244l\172\145j\176dh\016\190\243\237 \175\027\204vK\152M\200\239\025\186\236\139\012\020$\191/\2233\022\000q\174\006\160\030\204\028\187\238w\"3\024P'\217F\203\179\181\191\218c\\\143\180X\140\248@1\221%\131g\241\2304\219\197\138|J\175`^Q\134y\200\152\000\165\167\189oh\201\191$$\rK\164\1399\161\184\158|\017\021\226\028](\228\231\149\127\139Tb\139\014m\167\031\005u`\nJ!L\166H\029\029\001\219r3b\170\148O\225\229\138VG\209q\215\141\159\243w\193r\210\201\133\169E\182!\000\143c\207:\190\167'\202n%&\238\250`/\000\244;\207Eb\146\179\228\182\024\157fJ\201\175\134\255\027)\150@\215\015\149\017\224\181\198\164Y\189?iQ\031\226\224\165h\128\\\141uhS\001\199z\204p\014\024\222C\163\244l\163\2332\241\205<C\187\135\177\030%\176\156\252\201\250\1441cF\015\183\133\1648\187\231\212\131\027\188v\r/\218\157\224_pg\156\249\218\185\253y\172n\246\162\209mv\168Qd\172~#d{\007ot2\221\226\0180\178\255\199+w$e\215\167\153+\000\132F>\000+de\203\131\214\031\130\234e<)*<\246H\006\205\1705\219\186-\195'\020\201\213\155:\161\221a\198m[\n\170\234#]Px\184\245\161\216\b\002\217\217B\206\177O\205g\230\233f_\001\223\154ne\172c\197\139n\031\203a\\1\204i\213R\018/@\2558\133\235\179\204l\203\004\203\176\198i\152\027\026\019\011c\237\\2O\1372\132\131u\190\217\233\168>\189\023\162\006-7W\186I+\240kaT\135aJ\244\152\173>\003aH\138\202P\249\176u\234\211\169\134y\189\197<\221\012\166\216\214V\007\187U\198T\179HxKw2\139\199S*l\228\025\244\218\212j\213\193\253\129r\206\207\174W\236M\134\146\217\241C|\154\153+wd9\255\226\020\2193\164\182^?)\211\027\171\214\234\152X\024i\231v\199\244\142\147\203\209\238<,\004\251\184\136\186\019|\186\b\255\157\255z[\019d\014\016z\tV\240b\192\146\198\235% gH\019-\001\173\007\riy%\186\132\028\209R\tL\171\170\025\240\202\137\207\1663x\225\173\1648\217\179\177\142:\026\031B\190&_d\249\\N\239\198\025E\2073\183,\153\205\232\0016j@\133\150T(=Y\250B\171^#<mh\228\190\177\203\159\135\135@\242=D\011Y\131\254uw.\184\165w\213\136\015m\184\n\175\003\251cs\003\181\221\155r\171#\146\031\182k/\249U\1770\129\174\157pRi\b\004d\141\016C\196z\172\029\242\166I\000l\186\251\022\007\r\175\2013\198H\229\128\181\016\\\199!\0202\018Jt\027p\019}\237\215\239\209\019Y\221x$0\027\234\184\179\172\217\202V\012\163\241\t\200(\163\223\128&\235\188V\249Z7\n\209\1700zR\195\ng%u\142\172\007J\141.tW\162\191\022\193\253Z\236\176\027Q&\018|M\186\000e\181\180\163\002\1478\212s\21545R\143\014UY\142:_\2443Li\187\205\224\1523\251\186\235z\tq\187\191b\133+\020v\130b\181-]\226\177g\192-\227h\027-yO O\252}\1738j\236\173\026\183\028\133\236\229\135\236\1806aK\140\136/\212S\213\027~+\137\200C\164\014o\18944\2269&*\023W\226D\030\246\183\146\185[w\228\235[\140/\246\b\0069\214v\198\190zC\155\139\t@X\127\199\178\159\2206\194\203\200\135\238?\201\132b\021\231\127\022>\"\203\185mS\253\001Q\147=`\131\178%a\127Ij\225\206B\r3}\170s\250\244\212\233;<\174\167\176\015\247\247'\"\226^j\247jX\229\238\246\191c\168\184\011\239D\159m\151\\0\n\006wjG,F\245\232V\241KI\220\007\183k\218\014\166\028\022\017\148g]\nC<\179yW\r5\169|L\027\015\200R4\147\175Ec\163u$\145\1641\027d\203\150\147\n\230\159T\242\163\198\226\018^\000\248E\"6\206r\160\229\162\146Y:\135U\027\188SO\2509\019\169\025h\nK\223\011\247\137\217\170\192\019\184;\140&\211Y|\177\187|7\164\000\180A,/{\016\004\195%\201D\1931\188\022\138\017z\005\218u\149F\128\017\245p\210p\212j\221\241\163\012\188n\r|\000\014\231 {C\241\180\195XL\146n\000\231\031\211=X\156\201\253\236p\250\243\216F0<\000i\220A\217\152\232}\222o\004\209|\173\130\158\166\221j\170\016\207\017\140B\235ee\156C\007\001\156\183\210Y\202\206\185B\220\201VB`\133\197\232\024\130\015\1676\143\233~Z\132\237\138\139\024p\004P\018\209\000NHG\140\153\243\218\194\214\203\146\149r\170p\002\134\181\232\182 .\144d\178&\174\158k\127d\202\014jO\252\137o5\173e\223=u\026O\172\138;\134wX\2373\240\224\025\218\023\150\132\190;J\147\184\141\016\148\220H\242\216?\216;\135\136\019B\001\255^\245\182t\252d\138\239\1863l\253\128\251\137\222\171\251_p\182\251O\158]P\171x\024aC\191~po\020\140h\135>\n\192\137\001\251\168Tr\022\183p\173\248\164S\1440\2100\239\161q,\235x\130'\141B\159\128A\197\188\211\195g\164k\252.\197\206\171\129\001\135\254\233\017\132M\219\147\150B\241\222\167u\249Q\1772&\204m7@\188\166\2068\147\151\195\201\190m2\198k\015\244\202E>\173t\209\135\208\024\177\185\250\023x\163\187\206\177O|\2250\020\015\135\000\003S\210_\163\137\017\226\"\143\178\026\003\1534\214\242;n\147L\246\214O\128\003\b\242\170\157\028\184r(\174\bu\219\248\004\248y|.\183h\201\237\177bwJ\255U\191\239N-\228\b\241\178E\195$lv\227\188lx\183\249N(\143\238\1568d\197S\217<\182I\146g\213<\219f\149\207\165\252\225+\004\131\239\027\238\0188pU\222\023\136\005\226\206=3/\021d\231\022\134\22541\154\227\158D\\1\211\201'\220\185\190\178\153\023>\149\252z\178I+mT.d\127\019\234\148\142\011\231\208\150{\015PIv\221\156\173\197\140\030\1474\187=[\180\225\227PA{\175l\165\213L#\203%\142\004|\152-\000\228P\020\017\170\158}T\240p\136\b9\240_\137\n_3v\172\240\158\129\1405;.\147X\210Ir\175g\237\022wAi\206\020\024\007?\136\152\171\021\212\249iR9\186:W`r\1778\250\b:\230\173\022u\024N\030\153|}D\193\025\014#YH\170?\185\188T\132\216\2557\239m\227\029\246~%\130\228\030\175\173\157\n\007\028y6\t_T\209\242\006&yk\239\219r\028\238\253\158\164\247\180.\251\251\192o\147I\209`\029_\031\221Ez\130%W$\163\007\211\201\238\255\162\221\184\197\156\011\1945\148\135\028\1666x\195\137\198\163\148\233j\199\219x\n\170\n\229\253\bV,\170\239\004\024po\206\219\183d\016\1999'\224\255\199L\254\147 F\174GaJ\1510'\b\189~\147C\156t\138\176\1857=\006\255\197\212\006P\248\r\219Y\173\138\224\152ZS\128\215~Xf\198@\237\164\134j\131\222.kd\238\217\200%\151\229\178I\160\170\225c9q\024P\r\202\139`K\250l\134]\140\182\223\254\t\252;\239c\180-\012q\239\234\156U>\184<$\220\141I\027^B>\253\225S\235\159\164?[\176\204\146\135-8\127oV\181_(\000{\178P\bn\015F\133\141@\014\227A%\149t\031\199\250\1705\020+\232\160E\230 :3z\020\217-EY\026\196\184\028\218\196\177\n\254\139\030\029\194\016\163bS\007\184\128DV\134\198G\219\182\t\223\174c\162\2276\149J\181p\164\019uY\149\195\019U\001]\nw\251\212\bQ!t\188\172\148,\026\213\218;\248\134\182V\222\170f\"\170l\140\148c%`\147\011\011R\220\208\140\1316\014\165\2151{\152\211\"Q\186&\129\003\220\1782\018S\209\162\011 \012\235U\175\230\218\188\137\215>\152\217\210G\236m\b\003|B\135\015:M&\158\187\2067c1\252\1438\164\174\196T\227\214[m\b\138\252\132^\213\028{\206\221\173<\234\179L3\248W\002f\000\252\196\247\005k\199P\252\128\135,Gq\213\130\230\241\027\025|\139e\150\165\197\197\241vIZJ\n\031\128\231\173o{\208g\202V\020\188\198\030\169\t\151\129\206\027\020\250\179\000\1903_\128stC\182\223\224\027\246\019\194m\n&\225JO9\206\149\212\136\127)\222\154}\216\240\169\204\168\242\0285\172&\"\217\1271\243\161\182C\186\005\0017@:\249/\173K\249\176\186_q\179\171\185-\021\132\012\129\159\014\218\165\184\193Xm\160\149k|\148\182\016\147;\221H\201\254]\026\255\0225\2327i\154\171(\147\226[d\204Y\253\230\157'Mt{\209\007\207\219\224I:\199\166\172u~,9\163\242T\023\139o\209\028v\237\225\199N\140~R\206\211#\231s\014\022\\\165\2147QWNT\031}\244\217DO\141\250\154=\235\022\161\232I\182ei\238r\198\220\190\229j5_+\175\180\016\"\144\191\151\139\024\155A\151E\179\2268B\166\251\r\220\214\015d\180\253\031\129(\229X\224s\172\228C\150\242_g\158\152U\240kx\005n\147\163\152\031h)\250\241j\244\255z\006\236\1937\191e\174^\153F\152/|J\169\196*b\196\156\129\197\004)\134c\206d\tf\255\027\022u\232*\021\203\016\242\194\147\176\156\16945z\218jC\2028\016\139\146\170dRX\022\213\24461\243x\234\205\151\215\154\134\135Y*\184#\191\197n\212\174OI\229\144\004\234\215\210\160\015\183W\180\140\133^e\176\011\163\017\232\232S.geQu\r\149'\240A=]E\171\216\220\167\191\1378\1741\184\133Q\176L\135\170\227\232\b\151\255\234\204M\171\238\174W_\208\161\195\241\235\2234\216\182S\162\135b\020\185r\247\162^\168\135l\179\021\165TlqZ|Vf\229\239\021\165\176N\167;\023\224\\?\165%h\198\203\148\248\165X\244@\172\135\195\029\165,\253\159O\134\134\023&\213\164xr\219\230\238c!I:\029:\154(\127\145D\210\236W\226\238Z\243&\193\180\232\132/\1801\186\r\138\000\014\167\247\246#\208\220\185\167F\229\212\026\157\172\172\190\243\241e\173\030s\164\166\208<\1890wB\235\017z\204KwV\136\227O\175\173\226\165\230\018\030B\173\176\"\204\015\153\n\019\189\199\196\192\014`(\t\127\233i\219\212\177\007j\205t\216\"\020Ex^\178I(\1664g'ql&B@\163T/\235\234o\255V\152;\190\245\bjjn/-\239A\156\225\136\185\205k\173\014\207\238\194\000\187\248OA}\029\247BEtcU\177i0\133\223\143\197zMrx\151+\231ftm\243\172\219\189V\231\196$\140\168\151\210uL\178\189\232\002\170\227\231\211V\128\233\223\149{\166}\222\n\b\188\233\147\184\232\0305\166ez\011\188\214\"\2167\234\131\189\005\217e\190\182J[\194\170v\127\225\230N\005C]\165\203\019\185\179\166\020\149\172\1341\132\167Xt\231\255\217\022_\130\245~\015\252\178\176\253?/\134\193\205\030\214\196@\145\1402\185\245\139\164\236\029\153\168\239g&\201m\178\029\187,\221\212\240\198\196\141\1735Mr\021\151\019Bh\251\215\239\232X\191c?\154\241\\O\167s\004v\157\022^\159\184)\147\195i\192\192\134\245[{\222/\176\r\000C\027\214\242\221|\222^m\183yn\150j\r.\170\248d\151\161\163\bpW\177\012\\\158\158\205]U\243bD\177\235\147\n\017\190f\192V\166\029\217\203\163j\174C\168wjf)x\252\164\219\255\175[\132Z\158\203F\226W\131U\027\153\220\241qq\207$\207\226\226\198\201\198\197\197\163\249*#\"\139N2P\145\220\178w\239\211\144\183j\218\129\007\244\n\014d\191\204\147\161\172\163\185\172\\t\161L-\017\189\155|\241\127\166m\002\153\017]\253u.\183\2274J\023\030;\157[\206\194Na,\225\197\015\209\154\028\139\191.\183n_lT\209\240\134\184\192\201\242\149\241\221\201\173q\129\r\163%S@\214\237\224\195\018\190\r\242\163\192&\170\021\"\174\191C\239\196\197\190\019\250\027q\tkE\192\134B~\190\r\219\n/Y\004st\178t\184\227O:\\t\183\143\210Q\197p\151\244&)h\138\007\241/\141J\153\014\029w0\2527Y\206\216f_IG\021\199K\240\211U'\1319Y\127\239\201\003\155V\234\139\211\215\"Z$\236}\164\155\018\144PQ\213\216)O\237\021>\187\179,+\221D\153\163`\186\244k\137\020Fg~\020\2468,\173\220\183\155\159\253\218\166\224\196\018\0259U\r6+\222y\174\184*#994\208\229\1787Y\228+S\237\178pS\152x8XW\229\182\188\007\156\130\154\183\223\030,S\146\\N\b\014\255\248xbI\166M\147/3V\024\214\170\213\n\189a\155H\002\208\143\238uO\185\199\212En]\209i\129\146\141\136n\245\211\181\207p\130\"C7\171tU\166X\174s\018\136\208\029\185W\240\133o,\192\218?\145\000\1698R\200\136\250\233\2438\207\143Q\149-;\150E\023\1968\204\245lBH\029\144\131\000;\021%`\161U\234\244X\195\186\233\024\201\245\215N\143\1567|p\241(*h\199\131\019\011+g\206\025\157}4\254\227\241\153\225o\209\158\178P\151\251G\157u\0012}\161[\167\ne\148v\133E\146b\199)\234\160\2477\t\245\164\146\b\1907ol\2226GB(;\221\157i\150\222\210\223\144&\194\207\142%h\154\193\184\242#\155\254P\154v}\211k\193\241\180^\204|\r\226\183\243\219a\129\128\198\186\239E\230\244\1988\170\190)\202 M~\230@*p\2438L\166\254\025)9\023\193O\227\205\207\031\200\206.{0\250\208<CCq:\014!Z\244@\001?\217\149\022\255wU\208lq6\184O\208I\145\152g\203K\194\027 |\"\225\205(\015L\234*\159\150V>\199$\022\243\242\252)\1973\254{4~\218\228ZY\138i\190\">\213\185s\021\152\025\170`h2B\190\180X\187\146\197\140\136WL\246\234?\163\205\2359\254]z/\235`\1410\015\214C\159\233\219TT\221_P\203\016\195\163ux"
 
   let d_bf043adf1d8ba761903c6f3447bae9d3 = ".56111],111:[0,.45833,0,0,.55],112:[.19444,.45833,0,0,.56111],113:[.19444,.45833,0,0,.56111],114:[0,.45833,.01528,0,.37222],115:[0,.45833,0,0,.42167],116:[0,.58929,0,0,.40417],117:[0,.45833,0,0,.56111],118:[0,.45833,.01528,0,.5],119:[0,.45833,.01528,0,.74445],120:[0,.45833,0,0,.5],121:[.19444,.45833,.01528,0,.5],122:[0,.45833,0,0,.47639],126:[.35,.34444,0,0,.55],160:[0,0,0,0,.25],168:[0,.69444,0,0,.55],176:[0,.69444,0,0,.73334],180:[0,.69444,0,0,.55],184:[.17014,0,0,0,.48889],305:[0,.45833,0,0,.25556],567:[.19444,.45833,0,0,.28611],710:[0,.69444,0,0,.55],711:[0,.63542,0,0,.55],713:[0,.63778,0,0,.55],728:[0,.69444,0,0,.55],729:[0,.69444,0,0,.30556],730:[0,.69444,0,0,.73334],732:[0,.69444,0,0,.55],733:[0,.69444,0,0,.55],915:[0,.69444,0,0,.58056],916:[0,.69444,0,0,.91667],920:[0,.69444,0,0,.85556],923:[0,.69444,0,0,.67223],926:[0,.69444,0,0,.73334],928:[0,.69444,0,0,.79445],931:[0,.69444,0,0,.79445],933:[0,.69444,0,0,.85556],934:[0,.69444,0,0,.79445],936:[0,.69444,0,0,.85556],937:[0,.69444,0,0,.79445],8211:[0,.45833,.03056,0,.55],8212:[0,.45833,.03056,0,1.10001],8216:[0,.69444,0,0,.30556],8217:[0,.69444,0,0,.30556],8220:[0,.69444,0,0,.55834],8221:[0,.69444,0,0,.55834]},\"SansSerif-Italic\":{32:[0,0,0,0,.25],33:[0,.69444,.05733,0,.31945],34:[0,.69444,.00316,0,.5],35:[.19444,.69444,.05087,0,.83334],36:[.05556,.75,.11156,0,.5],37:[.05556,.75,.03126,0,.83334],38:[0,.69444,.03058,0,.75834],39:[0,.69444,.07816,0,.27778],40:[.25,.75,.13164,0,.38889],41:[.25,.75,.02536,0,.38889],42:[0,.75,.11775,0,.5],43:[.08333,.58333,.02536,0,.77778],44:[.125,.08333,0,0,.27778],45:[0,.44444,.01946,0,.33333],46:[0,.08333,0,0,.27778],47:[.25,.75,.13164,0,.5],48:[0,.65556,.11156,0,.5],49:[0,.65556,.11156,0,.5],50:[0,.65556,.11156,0,.5],51:[0,.65556,.11156,0,.5],52:[0,.65556,.11156,0,.5],53:[0,.65556,.11156,0,.5],54:[0,.65556,.11156,0,.5],55:[0,.65556,.11156,0,.5],56:[0,.65556,.11156,0,.5],57:[0,.65556,.11156,0,.5],58:[0,.44444,.02502,0,.27778],59:[.125,.44444,.02502,0,.27778],61:[-.13,.37,.05087,0,.77778],63:[0,.69444,.11809,0,.47222],64:[0,.69444,.07555,0,.66667],65:[0,.69444,0,0,.66667],66:[0,.69444,.08293,0,.66667],67:[0,.69444,.11983,0,.63889],68:[0,.69444,.07555,0,.72223],69:[0,.69444,.11983,0,.59722],70:[0,.69444,.13372,0,.56945],71:[0,.69444,.11983,0,.66667],72:[0,.69444,.08094,0,.70834],73:[0,.69444,.13372,0,.27778],74:[0,.69444,.08094,0,.47222],75:[0,.69444,.11983,0,.69445],76:[0,.69444,0,0,.54167],77:[0,.69444,.08094,0,.875],78:[0,.69444,.08094,0,.70834],79:[0,.69444,.07555,0,.73611],80:[0,.69444,.08293,0,.63889],81:[.125,.69444,.07555,0,.73611],82:[0,.69444,.08293,0,.64584],83:[0,.69444,.09205,0,.55556],84:[0,.69444,.13372,0,.68056],85:[0,.69444,.08094,0,.6875],86:[0,.69444,.1615,0,.66667],87:[0,.69444,.1615,0,.94445],88:[0,.69444,.13372,0,.66667],89:[0,.69444,.17261,0,.66667],90:[0,.69444,.11983,0,.61111],91:[.25,.75,.15942,0,.28889],93:[.25,.75,.08719,0,.28889],94:[0,.69444,.0799,0,.5],95:[.35,.09444,.08616,0,.5],97:[0,.44444,.00981,0,.48056],98:[0,.69444,.03057,0,.51667],99:[0,.44444,.08336,0,.44445],100:[0,.69444,.09483,0,.51667],101:[0,.44444,.06778,0,.44445],102:[0,.69444,.21705,0,.30556],103:[.19444,.44444,.10836,0,.5],104:[0,.69444,.01778,0,.51667],105:[0,.67937,.09718,0,.23889],106:[.19444,.67937,.09162,0,.26667],107:[0,.69444,.08336,0,.48889],108:[0,.69444,.09483,0,.23889],109:[0,.44444,.01778,0,.79445],110:[0,.44444,.01778,0,.51667],111:[0,.44444,.06613,0,.5],112:[.19444,.44444,.0389,0,.51667],113:[.19444,.44444,.04169,0,.51667],114:[0,.44444,.10836,0,.34167],115:[0,.44444,.0778,0,.38333],116:[0,.57143,.07225,0,.36111],117:[0,.44444,.04169,0,.51667],118:[0,.44444,.10836,0,.46111],119:[0,.44444,.10836,0,.68334],120:[0,.44444,.09169,0,.46111],121:[.19444,.44444,.10836,0,.46111],122:[0,.44444,.08752,0,.43472],126:[.35,.32659,.08826,0,.5],160:[0,0,0,0,.25],168:[0,.67937,.06385,0,.5],176:[0,.69444,0,0,.73752],184:[.17014,0,0,0,.44445],305:[0,.44444,.04169,0,.23889],567:[.19444,.44444,.04169,0,.26667],710:[0,.69444,.0799,0,.5],711:[0,.63194,.08432,0,.5],713:[0,.60889,.08776,0,.5],714:[0,.69444,.09205,0,.5],715:[0,.69444,0,0,.5],728:[0,"
@@ -358,7 +358,7 @@ module Internal = struct
     | "highlight.pack.js" | "/highlight.pack.js" -> Some [ d_6b9eea5bd2cdd91f629293ab3b8808d1; d_30baf6fb746860926fdd280eefc46735; d_7df05ceea77c14d78f1f1df8f98def4f; d_106b469c9254e3a72af1bc5085256cca; d_5fcd7eba230acf47d54c1897a9a9c394; d_df9507781455088adf4ca1bd7fc0a321; d_b223e3337242ba6cf0905995918760a5; d_d6a1be8caf2478248edb48ee82070d9e; d_98850966979dd224456f716b44220d69; d_9873a9ace25bcd721b8eeb6b8dad71cf; d_b23657c0bc089d459bc6099791f97c23; d_f9c0b1a6ea9c119cb0f7ead5c3dac542; d_80a0027403c5ad56c7da4589713b2348; d_fe8f6a1f53d067d447bae579dc60d6f0; ]
     | "katex.min.css" | "/katex.min.css" -> Some [ d_2d798108ddda42cb699f6ad4421e720e; d_b128d6f091a42be5d7a929703f09ac36; d_1476b6e94be68e530a90bd0723d69c88; d_e357f75b8a7d9a6031bbdc38adcf1422; d_ad152fcf832897f8629ca758460f3d22; d_7c9075f31df2a532c3135ae327c84a92; ]
     | "katex.min.js" | "/katex.min.js" -> Some [ d_0c2c3443b618aef3ac4519dd2b159bbe; d_a2070486fb8e9102cd1537ebd1216a96; d_48a6338945c47ceb84d335248c3d6873; d_ad48849637d7c8349cb3e6952d5c8699; d_32baa17e8a53bbd439c58b0d89bc0503; d_c7561e7d22eb89e10083cfba7680012c; d_d04b09d89ef0b9af8a297a3592a2e4b1; d_c0cf7351fa27f73a72840e453c4b15f3; d_fadfd470a088dde5c3755136ac4b6188; d_326148c9e075f26f4dd5ee3862f61cf6; d_a55141bd5690b03d71c9675038f73b3f; d_225bdd9918928e02697ef5570454bf56; d_bf8e1c09c2162b9bb4b6578a59cc8069; d_bb5a8ed07dc95fa6f9f51938da398a35; d_b93e718b1ddefad06d18d9736584ad78; d_e12a510e69c6b3e0210294eedc2c3be3; d_bf043adf1d8ba761903c6f3447bae9d3; d_80ae3e22d162129b593049c0dc7f2407; d_d7b447b6bfc36721f581470728505547; d_92e0c0a734f49413d685531ad3f0a03e; d_cabefc6c9607b95a33af32a8c8832767; d_a03f60fbbac88837b2763d52df2c0820; d_5795c26325c462426548bd12ff6ef7a1; d_c0939c104021af2b0d9b24c7102061f2; d_3a7455b94742964a6cc5e84e314a6cfb; d_dc2a908015f68e5bff245fff4e602604; d_96c4d8e2622ac6552ccf67643b20f09c; d_37935d98135b118d937e895f4bb55add; d_efe21915ced6043dcaa8ff576e7948c7; d_fe0aa5b4043d6894e289163dd38508b7; d_dc29762de1ae6c28b3b3cc202f52ac6f; d_2c5af911fa1596ad2eef3a7e342be949; d_01738333fc004372ab1ae8bc7d370677; d_0d6ec6387686b4173900d29c91f338ee; d_5f9942b4d85184e45b9addfc25ca6fd4; d_105a9e030400f28a404c6badd930fe01; d_79c029f6f746a52f4a8bc8b6280c5c88; d_3a50124eae7017a15bb92024b9f6c8ad; d_d1d8d575696cbb5a4994efc9e2862948; d_a6e92521674c97f4d1bd649490d8a987; d_8f38ae17980f4039d715823515fd56d0; d_a841840589a3efb0465e49e0d8f985b5; d_e33d592534625de6438003412e1d8813; d_5b12b53efc1e6da3a434634e81c2251b; d_c7270ab94b84005c36e6e864e6ea5b10; d_5e57240b8ff6745d663ebd2060201199; d_02c9bc01125e92ce389d2ac93e62d14b; d_0d4c13a0e6487657499a2f37795ab83b; d_8ff622534e1e1348711c11358657050b; d_a8b5fa32242a1d360076af4bdc9dafbe; d_725c52bce5d22dff34816d0cea74cf51; d_a6db9cb29ea27586d2138cf4f8710b12; d_31ee9944b6c75c4351486bc790988371; d_1005d4f63119125aeb03e8a2fa265969; d_9ff5a6ec97f55e01b81f13d9d3f0ff67; d_f361846717ba3e91093152df70d5aab3; d_e462cdcfecbc18ac1f1e447bf1ed3697; d_0d5bde992f9fa1c53103cd024ff5833b; d_1b66f4e8c1fbc1c74875f8da050cc1d0; d_bad0217136fdcd657898ee631bd512d1; d_428c2b0f069b4ffaef294dc85aef1e4b; d_cb988ca0480d611a7c52551adcc9ed48; d_cdc6e947cdb2e0bb7fae7f338ffa12a0; d_f56cd226d59f4d3190a095998f97ac56; d_f5d214c6b91ee7f61f5a433fcdd70682; d_f4caf2cb8610b6735641c064e6453b79; d_da739bd79e1901a19d34fbf2d1a16298; ]
-    | "odoc.css" | "/odoc.css" -> Some [ d_5ee72be1d823f909a47aa812eb50b6f6; d_0fdc0eeaf87b75b6c50e285b375f4e09; d_41cfd166777ab1d0e6a6b39070fbb41c; d_396665eb256e05372074b6eef49926af; d_bcdcf563a38bb540aacbb0c6c928e02e; ]
+    | "odoc.css" | "/odoc.css" -> Some [ d_5ee72be1d823f909a47aa812eb50b6f6; d_0fdc0eeaf87b75b6c50e285b375f4e09; d_41cfd166777ab1d0e6a6b39070fbb41c; d_702eeb76f1c77cb926fb148aa0d2af83; d_4022f9ddc62af63e4eed2e4c7fc5c582; ]
     | _ -> None
 
   let file_list = [ "fonts/KaTeX_AMS-Regular.woff2"; "fonts/KaTeX_Caligraphic-Bold.woff2"; "fonts/KaTeX_Caligraphic-Regular.woff2"; "fonts/KaTeX_Fraktur-Bold.woff2"; "fonts/KaTeX_Fraktur-Regular.woff2"; "fonts/KaTeX_Main-Bold.woff2"; "fonts/KaTeX_Main-BoldItalic.woff2"; "fonts/KaTeX_Main-Italic.woff2"; "fonts/KaTeX_Main-Regular.woff2"; "fonts/KaTeX_Math-BoldItalic.woff2"; "fonts/KaTeX_Math-Italic.woff2"; "fonts/KaTeX_SansSerif-Bold.woff2"; "fonts/KaTeX_SansSerif-Italic.woff2"; "fonts/KaTeX_SansSerif-Regular.woff2"; "fonts/KaTeX_Script-Regular.woff2"; "fonts/KaTeX_Size1-Regular.woff2"; "fonts/KaTeX_Size2-Regular.woff2"; "fonts/KaTeX_Size3-Regular.woff2"; "fonts/KaTeX_Size4-Regular.woff2"; "fonts/KaTeX_Typewriter-Regular.woff2"; "highlight.pack.js"; "katex.min.css"; "katex.min.js"; "odoc.css"; ]
@@ -395,7 +395,7 @@ let hash = function
   | "highlight.pack.js" | "/highlight.pack.js" -> Some "f7f17015c0de1023c93929e3725a9248"
   | "katex.min.css" | "/katex.min.css" -> Some "1a262c83aa48d3ba34dd01c2ec6087d8"
   | "katex.min.js" | "/katex.min.js" -> Some "0376fd70eef224e946e13788118db3d1"
-  | "odoc.css" | "/odoc.css" -> Some "46c002bdee57b8a20840530f91744c2d"
+  | "odoc.css" | "/odoc.css" -> Some "a6d6104ab38ebab2da0126b227256765"
   | _ -> None
 
 let size = function
@@ -422,5 +422,5 @@ let size = function
   | "highlight.pack.js" | "/highlight.pack.js" -> Some 54535
   | "katex.min.css" | "/katex.min.css" -> Some 20978
   | "katex.min.js" | "/katex.min.js" -> Some 270376
-  | "odoc.css" | "/odoc.css" -> Some 16820
+  | "odoc.css" | "/odoc.css" -> Some 17017
   | _ -> None
diff --git a/src/latex/generator.ml b/src/latex/generator.ml
index c110210669..54f2409c10 100644
--- a/src/latex/generator.ml
+++ b/src/latex/generator.ml
@@ -111,9 +111,9 @@ let elt_size (x : elt) =
   | List _ | Section _ | Verbatim _ | Raw _ | Code_block _ | Indented _
   | Description _ ->
       Large
-  | Table _ -> Huge
+  | Table _ | Layout_table _ -> Huge
 
-let table = function
+let layout_table = function
   | [] -> []
   | a :: _ as m ->
       let start = List.map (fun _ -> Empty) a in
@@ -128,7 +128,7 @@ let table = function
       in
       let filter_row row = filter_map filter_empty @@ List.combine mask row in
       let row_size = List.fold_left max Empty mask in
-      [ Table { row_size; tbl = List.map filter_row m } ]
+      [ Layout_table { row_size; tbl = List.map filter_row m } ]
 
 let txt ~verbatim ~in_source ws =
   if verbatim then [ Txt ws ]
@@ -169,10 +169,11 @@ let rec pp_elt ppf = function
   | Code_fragment x -> Raw.code_fragment pp ppf x
   | List { typ; items } -> list typ pp ppf items
   | Description items -> Raw.description pp ppf items
-  | Table { row_size = Large | Huge; tbl } -> large_table ppf tbl
-  | Table { row_size = Small | Empty; tbl } ->
+  | Table { align; data } -> Raw.small_table pp ppf (Some align, data)
+  | Layout_table { row_size = Large | Huge; tbl } -> large_table ppf tbl
+  | Layout_table { row_size = Small | Empty; tbl } ->
       if List.length tbl <= small_table_height_limit then
-        Raw.small_table pp ppf tbl
+        Raw.small_table pp ppf (None, tbl)
       else large_table ppf tbl
   | Label x -> Raw.label ppf x
   | Indented x -> Raw.indent pp ppf x
@@ -181,8 +182,8 @@ let rec pp_elt ppf = function
 
 and pp ppf = function
   | [] -> ()
-  | Break _ :: (Table _ :: _ as q) -> pp ppf q
-  | (Table _ as t) :: Break _ :: q -> pp ppf (t :: q)
+  | Break _ :: ((Layout_table _ | Table _) :: _ as q) -> pp ppf q
+  | ((Layout_table _ | Table _) as t) :: Break _ :: q -> pp ppf (t :: q)
   | Break a :: Break b :: q -> pp ppf (Break (max a b) :: q)
   | Ligaturable "-" :: Ligaturable ">" :: q ->
       Raw.rightarrow ppf;
@@ -296,6 +297,7 @@ let rec block ~in_source (l : Block.t) =
         @ if in_source then [] else [ Break Paragraph ]
     | List (typ, l) ->
         [ List { typ; items = List.map (block ~in_source:false) l } ]
+    | Table t -> table_block t
     | Description l ->
         [
           (let item i =
@@ -316,6 +318,18 @@ let rec block ~in_source (l : Block.t) =
   in
   list_concat_map l ~f:one
 
+and table_block { Table.data; align } =
+  let data =
+    List.map
+      (List.map (fun (cell, cell_type) ->
+           let content = block ~in_source:false cell in
+           match cell_type with
+           | `Header -> [ Style (`Bold, content) ]
+           | `Data -> content))
+      data
+  in
+  [ Table { align; data } ]
+
 let rec is_only_text l =
   let is_text : Item.t -> _ = function
     | Heading _ | Text _ -> true
@@ -380,7 +394,7 @@ let rec documentedSrc (t : DocumentedSrc.t) =
           let doc = [ block ~in_source:true dsrc.doc ] in
           (content @ label dsrc.anchor) :: doc
         in
-        table (List.map one l) @ to_latex rest
+        layout_table (List.map one l) @ to_latex rest
   in
   to_latex t
 
diff --git a/src/latex/raw.ml b/src/latex/raw.ml
index 9e6407eb39..ac6816d1b3 100644
--- a/src/latex/raw.ml
+++ b/src/latex/raw.ml
@@ -178,23 +178,35 @@ let input ppf x = create "input" latex_path ppf x
 let ocamltabular ~column_desc pp ppf x =
   env "ocamltabular" ~args:[ column_desc ] pp ppf x
 
-let small_table pp ppf tbl =
-  let columns = List.length (List.hd tbl) in
+let small_table pp ppf (alignment, tbl) =
+  let columns = match tbl with [] -> 1 | _ -> List.length (List.hd tbl) in
   let row ppf x =
     let ampersand ppf () = Fmt.pf ppf "& " in
     Fmt.list ~sep:ampersand pp ppf x;
     break ppf Line
   in
   let matrix ppf m = List.iter (row ppf) m in
-  let rec repeat n s ppf =
-    if n = 0 then () else Fmt.pf ppf "%t%t" s (repeat (n - 1) s)
-  in
-  let cell ppf =
-    Fmt.pf ppf "p{%.3f\\textwidth}" (1.0 /. float_of_int columns)
-  in
-  let table ppf tbl =
-    ocamltabular ~column_desc:(repeat columns cell) matrix ppf tbl
+  let column_desc =
+    let pp_alignment ppf align =
+      match align with
+      | Odoc_document.Types.Table.Default -> Fmt.pf ppf "p"
+      | Left -> Fmt.pf ppf "w{l}"
+      | Right -> Fmt.pf ppf "w{r}"
+      | Center -> Fmt.pf ppf "w{c}"
+    in
+    let cell ppf align =
+      Fmt.pf ppf "%a{%.3f\\textwidth}" pp_alignment align
+        (1.0 /. float_of_int columns)
+    in
+    match alignment with
+    | None ->
+        let rec repeat n s ppf =
+          if n = 0 then () else Fmt.pf ppf "%t%t" s (repeat (n - 1) s)
+        in
+        repeat columns (fun ppf -> cell ppf Default)
+    | Some alignment -> fun ppf -> List.iter (cell ppf) alignment
   in
+  let table ppf tbl = ocamltabular ~column_desc matrix ppf tbl in
   (* we add line breaks to never insert tables between delimiters,
      to avoid rendering:
           | `A
diff --git a/src/latex/raw.mli b/src/latex/raw.mli
index 65941310f8..c6c2196d26 100644
--- a/src/latex/raw.mli
+++ b/src/latex/raw.mli
@@ -63,7 +63,7 @@ val description : ('a, ('a * 'a) list) tr
 
 val item : 'a t with_options
 
-val small_table : ('a, 'a list list) tr
+val small_table : ('a, Types.alignment list option * 'a list list) tr
 
 val input : Fpath.t Fmt.t
 
diff --git a/src/latex/types.ml b/src/latex/types.ml
index d1e1c3e3e0..3ac77cf730 100644
--- a/src/latex/types.ml
+++ b/src/latex/types.ml
@@ -23,6 +23,7 @@ type elt =
   | List of list_info
   | Description of (t * t) list
   | Indented of t
+  | Layout_table of layout_table
   | Table of table
   | Ligaturable of string
 
@@ -30,7 +31,11 @@ and section = { level : int; label : string option; content : t }
 
 and list_info = { typ : Odoc_document.Types.Block.list_type; items : t list }
 
-and table = { row_size : row_size; tbl : t list list }
+and layout_table = { row_size : row_size; tbl : t list list }
+
+and alignment = Odoc_document.Types.Table.alignment
+
+and table = { align : alignment list; data : t list list }
 
 and t = elt list
 
diff --git a/src/manpage/generator.ml b/src/manpage/generator.ml
index 84fbe0cf0e..c23979863a 100644
--- a/src/manpage/generator.ml
+++ b/src/manpage/generator.ml
@@ -43,6 +43,8 @@ module Roff = struct
     | String of string
     | Vspace
     | Indent of int * t
+    | Align_line of string
+    | Table_cell of t
 
   let noop = Concat []
 
@@ -207,6 +209,13 @@ module Roff = struct
           | Macro (s, args) ->
               pp_macro ppf s "%s" args;
               newline_if ppf (not is_macro)
+          | Align_line s ->
+              Format.pp_print_string ppf (s ^ ".");
+              newline_if ppf (not is_macro)
+          | Table_cell c ->
+              Format.pp_print_text ppf "T{\n";
+              one ~indent ppf c;
+              Format.pp_print_text ppf "\nT}"
           | Indent (i, content) ->
               let indent = indent + i in
               one ~indent ppf content);
@@ -302,6 +311,53 @@ and inline (l : Inline.t) =
       | Math s -> math s ++ inline rest
       | Raw_markup t -> raw_markup t ++ inline rest)
 
+let table pp { Table.data; align } =
+  let sep = '\t' in
+  let alignment =
+    let alignment =
+      match align with
+      | align ->
+          List.map
+            (function
+              (* Since we are enclosing cells in text blocks, the alignment has
+                 no effect on the content of a sufficiently big cell, for some
+                 reason... (see the markup test in generators)
+
+                 One solution would be to use the [m] column specifier to apply
+                 a macro to the text blocks of the columns. Those macros would
+                 be [lj], [ce] or [rj], which define alignment. However, this
+                 breaks both the alignment for small table cells, and the
+                 largeness of columns. For the records, it woulb be:
+
+                 {[
+                   | Some `Left -> "lmlj"
+                   | Some `Center -> "cmce"
+                   | Some `Right -> "rmrj"
+                   | None -> "l"
+                  ]} *)
+              | Table.Left -> "l"
+              | Center -> "c"
+              | Right -> "r"
+              | Default -> "l")
+            align
+    in
+    Align_line (String.concat "" alignment)
+  in
+  env "TS" "TE" ""
+    (str "allbox;" ++ alignment
+    ++ List.fold_left
+         (fun acc row ->
+           acc ++ vspace
+           ++
+           match row with
+           | [] -> noop
+           | (h, _) :: t ->
+               List.fold_left
+                 (fun acc (x, _) -> acc ++ str "%c" sep ++ Table_cell (pp x))
+                 (Table_cell (pp h))
+                 t)
+         noop data)
+
 let rec block (l : Block.t) =
   match l with
   | [] -> noop
@@ -320,6 +376,7 @@ let rec block (l : Block.t) =
             indent 2 (bullet ++ sp ++ block b)
           in
           list ~sep:break (List.mapi f l) ++ continue rest
+      | Table t -> table block t ++ continue rest
       | Description _ ->
           let descrs, _, rest =
             Take.until l ~classify:(function
diff --git a/src/model/comment.ml b/src/model/comment.ml
index a95eff2123..990ef417e1 100644
--- a/src/model/comment.ml
+++ b/src/model/comment.ml
@@ -6,6 +6,8 @@ type 'a with_location = 'a Location_.with_location
 
 type style = [ `Bold | `Italic | `Emphasis | `Superscript | `Subscript ]
 
+type alignment = [ `Left | `Center | `Right ]
+
 type raw_markup_target = string
 
 type leaf_inline_element =
@@ -41,12 +43,22 @@ type module_reference = {
 (** The [{!modules: ...}] markup. [module_synopsis] is initially [None], it is
     resolved during linking. *)
 
+type 'a cell = 'a with_location list * [ `Header | `Data ]
+type 'a row = 'a cell list
+type 'a grid = 'a row list
+
+type 'a abstract_table = {
+  data : 'a grid;
+  align : alignment option list option;
+}
+
 type nestable_block_element =
   [ `Paragraph of paragraph
   | `Code_block of string option * string with_location
   | `Math_block of string
   | `Verbatim of string
   | `Modules of module_reference list
+  | `Table of nestable_block_element abstract_table
   | `List of
     [ `Unordered | `Ordered ] * nestable_block_element with_location list list
   ]
diff --git a/src/model/semantics.ml b/src/model/semantics.ml
index 9770fed63a..117cb26e04 100644
--- a/src/model/semantics.ml
+++ b/src/model/semantics.ml
@@ -19,6 +19,7 @@ let describe_internal_tag = function
   | `Inline -> "@inline"
   | `Open -> "@open"
   | `Closed -> "@closed"
+  | `Hidden -> "@hidden"
 
 let warn_unexpected_tag { Location.value; location } =
   Error.raise_warning
@@ -252,6 +253,14 @@ let rec nestable_block_element :
   | { value = `List (kind, _syntax, items); location } ->
       `List (kind, List.map (nestable_block_elements status) items)
       |> Location.at location
+  | { value = `Table ((grid, align), (`Heavy | `Light)); location } ->
+      let data =
+        List.map
+          (List.map (fun (cell, cell_type) ->
+               (nestable_block_elements status cell, cell_type)))
+          grid
+      in
+      `Table { Comment.data; align } |> Location.at location
 
 and nestable_block_elements status elements =
   List.map (nestable_block_element status) elements
@@ -476,7 +485,7 @@ let strip_internal_tags ast : internal_tags_removed with_location list * _ =
       -> (
         let next tag = loop ({ wloc with value = tag } :: tags) ast' tl in
         match tag with
-        | (`Inline | `Open | `Closed) as tag -> next tag
+        | (`Inline | `Open | `Closed | `Hidden) as tag -> next tag
         | `Canonical { Location.value = s; location = r_location } -> (
             match
               Error.raise_warnings (Reference.read_path_longident r_location s)
diff --git a/src/model_desc/comment_desc.ml b/src/model_desc/comment_desc.ml
index 28ee873228..daff4c7a2c 100644
--- a/src/model_desc/comment_desc.ml
+++ b/src/model_desc/comment_desc.ml
@@ -25,6 +25,7 @@ type general_block_element =
   | `Modules of Comment.module_reference list
   | `List of
     [ `Unordered | `Ordered ] * general_block_element with_location list list
+  | `Table of general_block_element abstract_table
   | `Heading of
     Comment.heading_attrs * Identifier.Label.t * general_link_content
   | `Tag of general_tag ]
@@ -113,6 +114,22 @@ let rec block_element : general_block_element t =
     | `Modules x -> C ("`Modules", x, List module_reference)
     | `List (x1, x2) ->
         C ("`List", (x1, (x2 :> general_docs list)), Pair (list_kind, List docs))
+    | `Table { data; align } ->
+        let cell_type_desc =
+          Variant (function `Header -> C0 "`Header" | `Data -> C0 "`Data")
+        in
+        let data_desc = List (List (Pair (docs, cell_type_desc))) in
+        let align_desc =
+          Option
+            (Variant
+               (function
+               | `Left -> C0 "`Left"
+               | `Center -> C0 "`Center"
+               | `Right -> C0 "`Right"))
+        in
+        let align_desc = List align_desc in
+        let table_desc = Pair (data_desc, Option align_desc) in
+        C ("`Table", (data, align), table_desc)
     | `Heading h -> C ("`Heading", h, heading)
     | `Tag x -> C ("`Tag", x, tag))
 
diff --git a/src/xref2/link.ml b/src/xref2/link.ml
index 5f896fc17a..fad010e488 100644
--- a/src/xref2/link.ml
+++ b/src/xref2/link.ml
@@ -242,6 +242,15 @@ and comment_nestable_block_element env parent ~loc:_
         ( x,
           List.rev_map (comment_nestable_block_element_list env parent) ys
           |> List.rev )
+  | `Table { data; align } ->
+      let data =
+        let map f x = List.rev_map f x |> List.rev in
+        map
+          (map (fun (cell, cell_type) ->
+               (comment_nestable_block_element_list env parent cell, cell_type)))
+          data
+      in
+      `Table { Comment.data; align }
   | `Modules refs ->
       let refs =
         List.rev_map
diff --git a/test/generators/cases/markup.mli b/test/generators/cases/markup.mli
index 00d03d9f14..81d20ec473 100644
--- a/test/generators/cases/markup.mli
+++ b/test/generators/cases/markup.mli
@@ -171,6 +171,49 @@ v}
     {!modules: X Y}
 
 
+    {1 Tables}
+
+    {t
+        Left | Center | Right | Default
+       :-----|:------:|------:|---------
+         A   |    B   |   C   |    D
+    }
+
+    {t
+        Left | Center | Right | Default
+       :-----|:------:|------:|---------
+         A   |    B   |   C   |    D
+         A much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it   |    B much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it   |   C much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it   |    D much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+    }
+
+    {t
+        No | Header
+        A  | B
+    }
+
+    {table
+      {tr
+        {th Header 1}
+        {th Header 2}
+      }
+      {tr
+        {td Data 1}
+        {td Data 2}
+      }
+    }
+
+    {table
+      {tr
+        {th Header 1}
+        {td Data 1}
+      }
+      {tr
+        {th Header 2}
+        {td Data 2}
+      }
+    }
+
+
     {1 Tags}
 
     Each comment can end with zero or more tags. Here are some examples:
diff --git a/test/generators/html/Markup.html b/test/generators/html/Markup.html
index 91a9f12ac5..cd38385dca 100644
--- a/test/generators/html/Markup.html
+++ b/test/generators/html/Markup.html
@@ -58,7 +58,7 @@ <h1>Module <code><span>Markup</span></code></h1>
     <li><a href="#unicode">Unicode</a></li>
     <li><a href="#raw-html">Raw HTML</a></li>
     <li><a href="#math">Math</a></li><li><a href="#modules">Modules</a></li>
-    <li><a href="#tags">Tags</a></li>
+    <li><a href="#tables">Tables</a></li><li><a href="#tags">Tags</a></li>
    </ul>
   </nav>
   <div class="odoc-content">
@@ -222,7 +222,65 @@ <h2 id="math"><a href="#math" class="anchor"></a>Math</h2>
    </ul>
    <ul class="modules"><li><a href="Markup-X.html"><code>X</code></a> </li>
     <li><a href="Markup-Y.html"><code>Y</code></a> </li>
-   </ul><h2 id="tags"><a href="#tags" class="anchor"></a>Tags</h2>
+   </ul><h2 id="tables"><a href="#tables" class="anchor"></a>Tables</h2>
+   <table class="odoc-table">
+    <tr><th style="text-align:left"><p>Left</p></th>
+     <th style="text-align:center"><p>Center</p></th>
+     <th style="text-align:right"><p>Right</p></th><th><p>Default</p></th>
+    </tr>
+    <tr><td style="text-align:left"><p>A</p></td>
+     <td style="text-align:center"><p>B</p></td>
+     <td style="text-align:right"><p>C</p></td><td><p>D</p></td>
+    </tr>
+   </table>
+   <table class="odoc-table">
+    <tr><th style="text-align:left"><p>Left</p></th>
+     <th style="text-align:center"><p>Center</p></th>
+     <th style="text-align:right"><p>Right</p></th><th><p>Default</p></th>
+    </tr>
+    <tr><td style="text-align:left"><p>A</p></td>
+     <td style="text-align:center"><p>B</p></td>
+     <td style="text-align:right"><p>C</p></td><td><p>D</p></td>
+    </tr>
+    <tr>
+     <td style="text-align:left">
+      <p>A much longer paragraph which will need to be wrapped and more
+        content and more content and some different content and we will
+        see what is does if we can see it
+      </p>
+     </td>
+     <td style="text-align:center">
+      <p>B much longer paragraph which will need to be wrapped and more
+        content and more content and some different content and we will
+        see what is does if we can see it
+      </p>
+     </td>
+     <td style="text-align:right">
+      <p>C much longer paragraph which will need to be wrapped and more
+        content and more content and some different content and we will
+        see what is does if we can see it
+      </p>
+     </td>
+     <td>
+      <p>D much longer paragraph which will need to be wrapped and more
+        content and more content and some different content and we will
+        see what is does if we can see it
+      </p>
+     </td>
+    </tr>
+   </table>
+   <table class="odoc-table">
+    <tr><td><p>No</p></td><td><p>Header</p></td></tr>
+    <tr><td><p>A</p></td><td><p>B</p></td></tr>
+   </table>
+   <table class="odoc-table">
+    <tr><th><p>Header 1</p></th><th><p>Header 2</p></th></tr>
+    <tr><td><p>Data 1</p></td><td><p>Data 2</p></td></tr>
+   </table>
+   <table class="odoc-table">
+    <tr><th><p>Header 1</p></th><td><p>Data 1</p></td></tr>
+    <tr><th><p>Header 2</p></th><td><p>Data 2</p></td></tr>
+   </table><h2 id="tags"><a href="#tags" class="anchor"></a>Tags</h2>
    <p>Each comment can end with zero or more tags. Here are some examples:
    </p>
    <ul class="at-tags">
diff --git a/test/generators/latex/Markup.tex b/test/generators/latex/Markup.tex
index c0e085b6e9..70ecd380fd 100644
--- a/test/generators/latex/Markup.tex
+++ b/test/generators/latex/Markup.tex
@@ -101,6 +101,96 @@ \subsection{Modules\label{modules}}%
 \makeatletter\advance\@topsepadd-\topsep\makeatother% topsep is hardcoded
 \item[{\hyperref[module-Markup-module-X]{\ocamlinlinecode{\ocamlinlinecode{X}}[p\pageref*{module-Markup-module-X}]}}]{}%
 \item[{\hyperref[module-Markup-module-Y]{\ocamlinlinecode{\ocamlinlinecode{Y}}[p\pageref*{module-Markup-module-Y}]}}]{}\end{description}%
+\subsection{Tables\label{tables}}\\
+\begin{ocamltabular}{w{l}{0.250\textwidth}w{c}{0.250\textwidth}w{r}{0.250\textwidth}p{0.250\textwidth}}\bold{Left
+
+}& \bold{Center
+
+}& \bold{Right
+
+}& \bold{Default
+
+}\\
+A
+
+& B
+
+& C
+
+& D
+
+\\
+\end{ocamltabular}%
+\\
+\\
+\begin{ocamltabular}{w{l}{0.250\textwidth}w{c}{0.250\textwidth}w{r}{0.250\textwidth}p{0.250\textwidth}}\bold{Left
+
+}& \bold{Center
+
+}& \bold{Right
+
+}& \bold{Default
+
+}\\
+A
+
+& B
+
+& C
+
+& D
+
+\\
+A much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+
+& B much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+
+& C much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+
+& D much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+
+\\
+\end{ocamltabular}%
+\\
+\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}No
+
+& Header
+
+\\
+A
+
+& B
+
+\\
+\end{ocamltabular}%
+\\
+\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\bold{Header 1
+
+}& \bold{Header 2
+
+}\\
+Data 1
+
+& Data 2
+
+\\
+\end{ocamltabular}%
+\\
+\\
+\begin{ocamltabular}{p{0.500\textwidth}p{0.500\textwidth}}\bold{Header 1
+
+}& Data 1
+
+\\
+\bold{Header 2
+
+}& Data 2
+
+\\
+\end{ocamltabular}%
+\\
 \subsection{Tags\label{tags}}%
 Each comment can end with zero or more tags. Here are some examples:
 
diff --git a/test/generators/man/Markup.3o b/test/generators/man/Markup.3o
index abc91204b8..e28eb65f17 100644
--- a/test/generators/man/Markup.3o
+++ b/test/generators/man/Markup.3o
@@ -250,7 +250,119 @@ Math elements can be inline: \int_{-\infty}^\infty, or blocks:
 .nf 
 .sp 
 .in 3
-\fB10 Tags\fR
+\fB10 Tables\fR
+.in 
+.sp 
+.fi 
+.TS 
+allbox;lcrl.
+.sp 
+T{
+Left
+T}	T{
+Center
+T}	T{
+Right
+T}	T{
+Default
+T}
+.sp 
+T{
+A
+T}	T{
+B
+T}	T{
+C
+T}	T{
+D
+T}
+.TE 
+.sp 
+.TS 
+allbox;lcrl.
+.sp 
+T{
+Left
+T}	T{
+Center
+T}	T{
+Right
+T}	T{
+Default
+T}
+.sp 
+T{
+A
+T}	T{
+B
+T}	T{
+C
+T}	T{
+D
+T}
+.sp 
+T{
+A much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+T}	T{
+B much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+T}	T{
+C much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+T}	T{
+D much longer paragraph which will need to be wrapped and more content and more content and some different content and we will see what is does if we can see it
+T}
+.TE 
+.sp 
+.TS 
+allbox;ll.
+.sp 
+T{
+No
+T}	T{
+Header
+T}
+.sp 
+T{
+A
+T}	T{
+B
+T}
+.TE 
+.sp 
+.TS 
+allbox;ll.
+.sp 
+T{
+Header 1
+T}	T{
+Header 2
+T}
+.sp 
+T{
+Data 1
+T}	T{
+Data 2
+T}
+.TE 
+.sp 
+.TS 
+allbox;ll.
+.sp 
+T{
+Header 1
+T}	T{
+Data 1
+T}
+.sp 
+T{
+Header 2
+T}	T{
+Data 2
+T}
+.TE 
+.nf 
+.sp 
+.in 3
+\fB11 Tags\fR
 .in 
 .sp 
 .fi