From d146f6de2ecdfb586682e966e3b51a5575d7455c Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 7 Mar 2025 13:36:28 +0100 Subject: [PATCH 01/53] Add markdown integration test --- test/integration/markdown.t/run.t | 11 +++++++++++ test/integration/markdown.t/test.mli | 10 ++++++++++ test/integration/markdown.t/test2.mli | 3 +++ 3 files changed, 24 insertions(+) create mode 100644 test/integration/markdown.t/run.t create mode 100644 test/integration/markdown.t/test.mli create mode 100644 test/integration/markdown.t/test2.mli diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t new file mode 100644 index 0000000000..f9d3e114b8 --- /dev/null +++ b/test/integration/markdown.t/run.t @@ -0,0 +1,11 @@ + $ ocamlc -c -bin-annot test.mli + $ ocamlc -c -bin-annot test2.mli + $ printf "{0 The title}\n" > page.mld + $ odoc compile --package test test.cmti + $ odoc compile --package test -I . test2.cmti + $ odoc compile --package test -I . page.mld + $ odoc link test.odoc + $ odoc link test2.odoc + $ odoc link page-page.odoc + $ odoc markdown-generate test.odocl -o markdown + $ ls markdown diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli new file mode 100644 index 0000000000..081a2c018f --- /dev/null +++ b/test/integration/markdown.t/test.mli @@ -0,0 +1,10 @@ +(** Test *) + +(** {1 Section 1} *) + +type t + +(** {1 Section 2} *) + +type u + diff --git a/test/integration/markdown.t/test2.mli b/test/integration/markdown.t/test2.mli new file mode 100644 index 0000000000..dfbac3c757 --- /dev/null +++ b/test/integration/markdown.t/test2.mli @@ -0,0 +1,3 @@ +val v : Test.t + + From aa56f99dedf61c795de737e9113bf9a00541c941 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 7 Mar 2025 13:36:51 +0100 Subject: [PATCH 02/53] Add markdown derived from html output --- src/markdown2/config.ml | 7 + src/markdown2/dune | 4 + src/markdown2/generator.ml | 701 ++++++++++++++++++++++++++++++ src/markdown2/generator.mli | 25 ++ src/markdown2/link.ml | 125 ++++++ src/markdown2/link.mli | 15 + src/markdown2/markdown_page.ml | 269 ++++++++++++ src/markdown2/markdown_page.mli | 47 ++ src/markdown2/markdown_source.ml | 81 ++++ src/markdown2/markdown_source.mli | 5 + src/markdown2/odoc_markdown.ml | 10 + src/markdown2/sidebar.ml | 25 ++ src/markdown2/sidebar.mli | 1 + src/markdown2/types.ml | 24 + 14 files changed, 1339 insertions(+) create mode 100644 src/markdown2/config.ml create mode 100644 src/markdown2/dune create mode 100644 src/markdown2/generator.ml create mode 100644 src/markdown2/generator.mli create mode 100644 src/markdown2/link.ml create mode 100644 src/markdown2/link.mli create mode 100644 src/markdown2/markdown_page.ml create mode 100644 src/markdown2/markdown_page.mli create mode 100644 src/markdown2/markdown_source.ml create mode 100644 src/markdown2/markdown_source.mli create mode 100644 src/markdown2/odoc_markdown.ml create mode 100644 src/markdown2/sidebar.ml create mode 100644 src/markdown2/sidebar.mli create mode 100644 src/markdown2/types.ml diff --git a/src/markdown2/config.ml b/src/markdown2/config.ml new file mode 100644 index 0000000000..c85427449b --- /dev/null +++ b/src/markdown2/config.ml @@ -0,0 +1,7 @@ +(* Markdown output configuration *) + +[@@@warning "-69"] + +type t = { root_url : string option } + +let v ~root_url () = { root_url } diff --git a/src/markdown2/dune b/src/markdown2/dune new file mode 100644 index 0000000000..2836410dcf --- /dev/null +++ b/src/markdown2/dune @@ -0,0 +1,4 @@ +(library + (name odoc_markdown) + (public_name odoc.markdown) + (libraries odoc_model odoc_document cmarkit)) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml new file mode 100644 index 0000000000..3d785f52c8 --- /dev/null +++ b/src/markdown2/generator.ml @@ -0,0 +1,701 @@ +(* + * Copyright (c) 2016 Thomas Refis + * + * Permission to use, copy, modify, and distribute this software for any + * purpose with or without fee is hereby granted, provided that the above + * copyright notice and this permission notice appear in all copies. + * + * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES + * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF + * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR + * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES + * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN + * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF + * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. + *) + +[@@@warning "-32-26-27"] + +open Odoc_utils + +module HLink = Link +open Odoc_document.Types +module Html = Tyxml.Html +module Doctree = Odoc_document.Doctree +module Url = Odoc_document.Url +module Link = HLink +module Blocks = Cmarkit.Block + +type any = Html_types.flow5 + +type item = Html_types.flow5_without_header_footer + +type flow = Html_types.flow5_without_sectioning_heading_header_footer + +type phrasing = Html_types.phrasing + +type non_link_phrasing = Html_types.phrasing_without_interactive + +let mk_anchor_link id = + [ Html.a ~a:[ Html.a_href ("#" ^ id); Html.a_class [ "anchor" ] ] [] ] + +let mk_anchor anchor = + match anchor with + | None -> ([], [], []) + | Some { Url.Anchor.anchor; _ } -> + let link = mk_anchor_link anchor in + let extra_attr = [ Html.a_id anchor ] in + let extra_class = [ "anchored" ] in + (extra_attr, extra_class, link) + +let mk_link_to_source ~config ~resolve anchor = + match anchor with + | None -> [] + | Some url -> + let href = Link.href ~config ~resolve url in + [ + Html.a + ~a:[ Html.a_href href; Html.a_class [ "source_link" ] ] + [ Html.txt "Source" ]; + ] + +let class_ (l : Class.t) = if l = [] then [] else [ Html.a_class l ] + +let inline_math (s : Math.t) = + Html.code ~a:[ Html.a_class [ "odoc-katex-math" ] ] [ Html.txt s ] + +let block_math (s : Math.t) = + Html.pre ~a:[ Html.a_class [ "odoc-katex-math"; "display" ] ] [ Html.txt s ] + +and raw_markup (t : Raw_markup.t) = + let target, content = t in + match Astring.String.Ascii.lowercase target with + | "html" -> + (* This is OK because we output *textual* HTML. + In theory, we should try to parse the HTML with lambdasoup and rebuild + the HTML tree from there. + *) + [ Html.Unsafe.data content ] + | _ -> [] + +and source k ?a (t : Source.t) = + let rec token (x : Source.token) = + match x with + | Elt i -> k i + | Tag (None, l) -> + let content = tokens l in + if content = [] then [] else [ Html.span content ] + | Tag (Some s, l) -> [ Html.span ~a:[ Html.a_class [ s ] ] (tokens l) ] + and tokens t = List.concat_map token t in + match tokens t with [] -> [] | l -> [ Html.code ?a l ] + +and styled style ~emph_level = + match style with + | `Emphasis -> + let a = if emph_level mod 2 = 0 then [] else [ Html.a_class [ "odd" ] ] in + (emph_level + 1, Html.em ~a) + | `Bold -> (emph_level, Html.b ~a:[]) + | `Italic -> (emph_level, Html.i ~a:[]) + | `Superscript -> (emph_level, Html.sup ~a:[]) + | `Subscript -> (emph_level, Html.sub ~a:[]) + +let rec internallink ~config ~emph_level ~resolve ?(a = []) target content + tooltip = + let a = match tooltip with Some s -> Html.a_title s :: a | None -> a in + let elt = + match target with + | Target.Resolved uri -> + let href = Link.href ~config ~resolve uri in + let content = inline_nolink ~emph_level content in + + let a = + Html.a_href href :: (a :> Html_types.a_attrib Html.attrib list) + in + Html.a ~a content + | Unresolved -> + (* let title = + * Html.a_title (Printf.sprintf "unresolved reference to %S" + * (ref_to_string ref) + * in *) + let a = Html.a_class [ "xref-unresolved" ] :: a in + Html.span ~a (inline ~config ~emph_level ~resolve content) + in + [ (elt :> phrasing Html.elt) ] + +and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : + phrasing Html.elt list = + let one (t : Inline.one) = + let a = class_ t.attr in + match t.desc with + | Text "" -> [] + | Text s -> + if a = [] then [ Html.txt s ] else [ Html.span ~a [ Html.txt s ] ] + | Entity s -> + if a = [] then [ Html.entity s ] else [ Html.span ~a [ Html.entity s ] ] + | Linebreak -> [ Html.br ~a () ] + | Styled (style, c) -> + let emph_level, app_style = styled style ~emph_level in + [ app_style @@ inline ~config ~emph_level ~resolve c ] + | Link { target = External href; content = c; _ } -> + let a = (a :> Html_types.a_attrib Html.attrib list) in + let content = inline_nolink ~emph_level c in + [ Html.a ~a:(Html.a_href href :: a) content ] + | Link { target = Internal t; content; tooltip } -> + internallink ~config ~emph_level ~resolve ~a t content tooltip + | Source c -> source (inline ~config ~emph_level ~resolve) ~a c + | Math s -> [ inline_math s ] + | Raw_markup r -> raw_markup r + in + List.concat_map one l + +and inline_nolink ?(emph_level = 0) (l : Inline.t) : + non_link_phrasing Html.elt list = + let one (t : Inline.one) = + let a = class_ t.attr in + match t.desc with + | Text "" -> [] + | Text s -> + if a = [] then [ Html.txt s ] else [ Html.span ~a [ Html.txt s ] ] + | Entity s -> + if a = [] then [ Html.entity s ] else [ Html.span ~a [ Html.entity s ] ] + | Linebreak -> [ Html.br ~a () ] + | Styled (style, c) -> + let emph_level, app_style = styled style ~emph_level in + [ app_style @@ inline_nolink ~emph_level c ] + | Link _ -> assert false + | Source c -> source (inline_nolink ~emph_level) ~a c + | Math s -> [ inline_math s ] + | Raw_markup r -> raw_markup r + in + List.concat_map one l + +let heading ~config ~resolve (h : Heading.t) = + let a, anchor = + match h.label with + | Some id -> ([ Html.a_id id ], mk_anchor_link id) + | None -> ([], []) + in + let content = inline ~config ~resolve h.title in + let source_link = mk_link_to_source ~config ~resolve h.source_anchor in + let mk = + match h.level with + | 0 -> Html.h1 + | 1 -> Html.h2 + | 2 -> Html.h3 + | 3 -> Html.h4 + | 4 -> Html.h5 + | _ -> Html.h6 + 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) = + let mk_block ?(extra_class = []) mk content = + let a = Some (class_ (extra_class @ t.attr)) in + [ mk ?a content ] + in + let mk_media_block media_block target alt = + let block = + match target with + | Target.External url -> media_block url alt + | Internal (Resolved uri) -> + let url = Link.href ~config ~resolve uri in + media_block url alt + | Internal Unresolved -> + let content = [ Html.txt alt ] in + let a = Html.a_class [ "xref-unresolved" ] :: [] in + [ Html.span ~a content ] + in + mk_block Html.div block + in + match t.desc with + | Inline i -> + if t.attr = [] then as_flow @@ inline ~config ~resolve i + else mk_block Html.span (inline ~config ~resolve i) + | Paragraph i -> mk_block Html.p (inline ~config ~resolve i) + | 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 + let term = + (inline ~config ~resolve i.Description.key + : phrasing Html.elt list + :> flow Html.elt list) + in + let def = block ~config ~resolve i.Description.definition in + Html.li ~a (term @ (Html.txt " " :: def)) + in + mk_block Html.ul (List.map item l) + | Raw_markup r -> raw_markup r + | Verbatim s -> mk_block Html.pre [ Html.txt s ] + | Source (lang_tag, c) -> + let extra_class = [ "language-" ^ lang_tag ] in + mk_block ~extra_class Html.pre (source (inline ~config ~resolve) c) + | Math s -> mk_block Html.div [ block_math s ] + | Audio (target, alt) -> + let audio src alt = + [ + Html.audio ~src + ~a:[ Html.a_controls (); Html.a_aria "label" [ alt ] ] + []; + ] + in + mk_media_block audio target alt + | Video (target, alt) -> + let video src alt = + [ + Html.video ~src + ~a:[ Html.a_controls (); Html.a_aria "label" [ alt ] ] + []; + ] + in + mk_media_block video target alt + | Image (target, alt) -> + let image src alt = + let img = + Html.a + ~a:[ Html.a_href src; Html.a_class [ "img-link" ] ] + [ Html.img ~src ~alt () ] + in + [ img ] + in + mk_media_block image target alt + in + + List.concat_map one l + +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 +*) +let flow_to_item : flow Html.elt list -> item Html.elt list = + fun x -> Html.totl @@ Html.toeltl x + +let div : (Html_types.div_attrib, [< item ], [> Html_types.div ]) Html.star = + Html.Unsafe.node "div" + +let spec_class attr = class_ ("spec" :: attr) + +let spec_doc_div ~config ~resolve = function + | [] -> [] + | docs -> + let a = [ Html.a_class [ "spec-doc" ] ] in + [ div ~a (flow_to_item @@ block ~config ~resolve docs) ] + +let rec documentedSrc ~config ~resolve (t : DocumentedSrc.t) : + item Html.elt list = + let open DocumentedSrc in + let take_code l = + Doctree.Take.until l ~classify:(function + | Code code -> Accum code + | Alternative (Expansion { summary; _ }) -> Accum summary + | _ -> Stop_and_keep) + in + let take_descr l = + Doctree.Take.until l ~classify:(function + | Documented { attrs; anchor; code; doc; markers } -> + Accum + [ { DocumentedSrc.attrs; anchor; code = `D code; doc; markers } ] + | Nested { attrs; anchor; code; doc; markers } -> + Accum + [ { DocumentedSrc.attrs; anchor; code = `N code; doc; markers } ] + | _ -> Stop_and_keep) + in + let rec to_html t = + match t with + | [] -> [] + | (Code _ | Alternative _) :: _ -> + let code, _, rest = take_code t in + source (inline ~config ~resolve) code @ to_html rest + | Subpage subp :: _ -> subpage ~config ~resolve subp + | (Documented _ | Nested _) :: _ -> + let l, _, rest = take_descr t in + let one { DocumentedSrc.attrs; anchor; code; doc; markers } = + let content = + match code with + | `D code -> (inline ~config ~resolve code :> item Html.elt list) + | `N n -> to_html n + in + let doc = + match doc with + | [] -> [] + | doc -> + let opening, closing = markers in + let delim s = + [ Html.span ~a:(class_ [ "comment-delim" ]) [ Html.txt s ] ] + in + [ + Html.div ~a:(class_ [ "def-doc" ]) + (delim opening @ block ~config ~resolve doc @ delim closing); + ] + in + let extra_attr, extra_class, link = mk_anchor anchor in + let content = (content :> any Html.elt list) in + Html.li + ~a:(extra_attr @ class_ (attrs @ extra_class)) + (link @ content @ doc) + in + Html.ol (List.map one l) :: to_html rest + in + to_html t + +and subpage ~config:_ ~resolve:_ (_subp : Subpage.t) = + (* items ~config ~resolve subp.content.items *) + [] + +(* I will be right back *) + +and items ~config ~resolve l : Blocks.t list = + let rec walk_items acc (t : Item.t list) = + let continue_with rest elts = + (walk_items [@tailcall]) (List.rev_append elts acc) rest + in + match t with + | [] -> List.rev acc + | Text _ :: _ as t -> + let text, _, rest = + Doctree.Take.until t ~classify:(function + | Item.Text text -> Accum text + | _ -> Stop_and_keep) + in + (* let content = flow_to_item @@ block ~config ~resolve text in *) + (* let inline = Cmarkit.Inline.(Text "asdf") in *) + (* let text = Cmarkit.Inline.text "This is paragraph text" in + let inline = Cmarkit.Inline.of_text text in + let content = Cmarkit.Block.paragraph inline in *) + let content = [ Blocks.empty ] in + (continue_with [@tailcall]) rest content + | Heading h :: rest -> + let headings = [ Blocks.empty ] in + (continue_with [@tailcall]) rest headings + | Include + { + attr; + anchor; + source_anchor; + doc; + content = { summary; status; content }; + } + :: rest -> + let doc = spec_doc_div ~config ~resolve doc in + let included_html = items content in + let a_class = + if List.length content = 0 then [ "odoc-include"; "shadowed-include" ] + else [ "odoc-include" ] + in + let content = [ Blocks.empty ] in + (* let content = + let details ~open' = + let open' = if open' then [ Html.a_open () ] else [] in + let summary = + let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let link_to_source = + mk_link_to_source ~config ~resolve source_anchor + in + let a = spec_class (attr @ extra_class) @ extra_attr in + Html.summary ~a @@ anchor_link @ link_to_source + @ source (inline ~config ~resolve) summary + in + let inner = + [ + Html.details ~a:open' summary + (included_html :> any Html.elt list); + ] + in + [ Html.div ~a:[ Html.a_class a_class ] (doc @ inner) ] + in + match status with + | `Inline -> doc @ included_html + | `Closed -> details ~open':false + | `Open -> details ~open':true + | `Default -> details ~open':true (* (Config.open_details config) *) + in *) + (continue_with [@tailcall]) rest content + | Declaration { Item.attr; anchor; source_anchor; content; doc } :: rest -> + let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let link_to_source = mk_link_to_source ~config ~resolve source_anchor in + let a = spec_class (attr @ extra_class) @ extra_attr in + let content = + anchor_link @ link_to_source @ documentedSrc ~config ~resolve content + in + let spec = [ Blocks.empty ] in + (* let spec = + let doc = spec_doc_div ~config ~resolve doc in + [ div ~a:[ Html.a_class [ "odoc-spec" ] ] (div ~a content :: doc) ] + in *) + (continue_with [@tailcall]) rest spec + and items l = walk_items [] l in + items l + +module Toc = struct + open Odoc_document.Doctree + open Types + + let on_sub : Subpage.status -> bool = function + | `Closed | `Open | `Default -> false + | `Inline -> true + + let gen_toc ~config ~resolve ~path i = + let toc = Toc.compute path ~on_sub i in + let rec section { Toc.url; text; children } = + let text = inline_nolink text in + let title = + (text + : non_link_phrasing Html.elt list + :> Html_types.flow5_without_interactive Html.elt list) + in + let title_str = + List.map (Format.asprintf "%a" (Tyxml.Html.pp_elt ())) text + |> String.concat ~sep:"" + in + let href = Link.href ~config ~resolve url in + { title; title_str; href; children = List.map section children } + in + List.map section toc +end + +module Breadcrumbs = struct + open Types + + let page_parent (page : Url.Path.t) = + let page = + match page with + | { parent = Some parent; name = "index"; kind = `LeafPage } -> parent + | _ -> page + in + match page with + | { parent = None; name = "index"; kind = `LeafPage } -> None + | { parent = Some parent; _ } -> Some parent + | { parent = None; _ } -> + Some { Url.Path.parent = None; name = "index"; kind = `LeafPage } + + let home_breadcrumb ~home_name config ~current_path ~home_path = + let href = + Some + (Link.href ~config ~resolve:(Current current_path) + (Odoc_document.Url.from_path home_path)) + in + { href; name = [ Html.txt home_name ]; kind = `LeafPage } + + let gen_breadcrumbs_no_sidebar ~config ~url = + let url = + match url with + | { Url.Path.name = "index"; parent = Some parent; kind = `LeafPage } -> + parent + | _ -> url + in + match url with + | { Url.Path.name = "index"; parent = None; kind = `LeafPage } -> + let kind = `LeafPage in + let current = { href = None; name = [ Html.txt "" ]; kind } in + { parents = []; up_url = None; current } + | url -> ( + (* This is the pre 3.0 way of computing the breadcrumbs *) + let rec get_parent_paths x = + match x with + | [] -> [] + | x :: xs -> ( + match Odoc_document.Url.Path.of_list (List.rev (x :: xs)) with + | Some x -> x :: get_parent_paths xs + | None -> get_parent_paths xs) + in + let to_breadcrumb path = + let href = + Some + (Link.href ~config ~resolve:(Current url) + (Odoc_document.Url.from_path path)) + in + { href; name = [ Html.txt path.name ]; kind = path.kind } + in + let parent_paths = + get_parent_paths (List.rev (Odoc_document.Url.Path.to_list url)) + |> List.rev + in + match List.rev parent_paths with + | [] -> assert false + | current :: parents -> + let up_url = + match page_parent current with + | None -> None + | Some up -> + Some + (Link.href ~config ~resolve:(Current url) + (Odoc_document.Url.from_path up)) + in + let current = to_breadcrumb current in + let parents = List.map to_breadcrumb parents |> List.rev in + let home = + home_breadcrumb ~home_name:"Index" config ~current_path:url + ~home_path: + { Url.Path.name = "index"; parent = None; kind = `LeafPage } + in + { current; parents = home :: parents; up_url }) + + let gen_breadcrumbs_with_sidebar ~config ~sidebar ~url:current_url = + let find_parent = + List.find_opt (function + | ({ node = { url = { page; anchor = ""; _ }; _ }; _ } : + Odoc_document.Sidebar.entry Tree.t) + when Url.Path.is_prefix page current_url -> + true + | _ -> false) + in + let rec extract acc (tree : Odoc_document.Sidebar.t) = + let parent = + match find_parent tree with + | Some { node = { url; valid_link; content; _ }; children } -> + let href = + if valid_link then + Some (Link.href ~config ~resolve:(Current current_url) url) + else None + in + let name = inline_nolink content in + let breadcrumb = { href; name; kind = url.page.kind } in + if url.page = current_url then Some (`Current breadcrumb) + else Some (`Parent (breadcrumb, children)) + | _ -> None + in + match parent with + | Some (`Parent (bc, children)) -> extract (bc :: acc) children + | Some (`Current current) -> + let up_url = + List.find_map (fun (b : Types.breadcrumb) -> b.href) acc + in + { Types.current; parents = List.rev acc; up_url } + | None -> + let kind = current_url.kind and name = current_url.name in + let current = { href = None; name = [ Html.txt name ]; kind } in + let up_url = + List.find_map (fun (b : Types.breadcrumb) -> b.href) acc + in + let parents = List.rev acc in + { Types.current; parents; up_url } + in + let escape = [] in + extract escape sidebar + + let gen_breadcrumbs ~config ~sidebar ~url = + match sidebar with + | None -> gen_breadcrumbs_no_sidebar ~config ~url + | Some sidebar -> gen_breadcrumbs_with_sidebar ~config ~sidebar ~url +end + +module Page = struct + let on_sub = function + | `Page _ -> None + | `Include x -> ( + match x.Include.status with + | `Closed | `Open | `Default -> None + | `Inline -> Some 0) + + let rec include_ ~config ~sidebar { Subpage.content; _ } = + page ~config ~sidebar content + + and subpages ~config ~sidebar subpages = + List.map (include_ ~config ~sidebar) subpages + + and page ~config ~sidebar p : Odoc_document.Renderer.page = + let { Page.preamble = _; items = i; url; source_anchor } = + Doctree.Labels.disambiguate_page ~enter_subpages:false p + in + let subpages = subpages ~config ~sidebar @@ Doctree.Subpages.compute p in + let resolve = Link.Current url in + let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~sidebar ~url in + let sidebar = + (* match sidebar with + | None -> None + | Some sidebar -> + let sidebar = Odoc_document.Sidebar.to_block sidebar url in + (Some (block ~config ~resolve sidebar) :> any Html.elt list option) *) + None + in + let i = Doctree.Shift.compute ~on_sub i in + let uses_katex = Doctree.Math.has_math_elements p in + let toc = Toc.gen_toc ~config ~resolve ~path:url i in + let content = items ~config ~resolve i in + let content = + (* Cmarkit.Doc.empty *) + Cmarkit.Doc.of_string ~layout:true ~strict:false "## Markdown" + in + let header, preamble = Doctree.PageTitle.render_title ?source_anchor p in + let header = items ~config ~resolve header in + let preamble = items ~config ~resolve preamble in + Markdown_page.make ~sidebar ~config ~header:(header @ preamble) ~toc + ~breadcrumbs ~url ~uses_katex content subpages + + and source_page ~config ~sidebar sp = + let { Source_page.url; contents } = sp in + let resolve = Link.Current sp.url in + let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~sidebar ~url in + let sidebar = + (* match sidebar with + | None -> None + | Some sidebar -> + let sidebar = Odoc_document.Sidebar.to_block sidebar url in + (Some (block ~config ~resolve sidebar) :> any Html.elt list option) *) + None + in + let title = url.Url.Path.name and doc = [ Blocks.empty ] in + (* and doc = Markdown_source.html_of_doc ~config ~resolve contents in *) + let header = + (* items ~config ~resolve (Doctree.PageTitle.render_src_title sp) *) + [] + in + Markdown_page.make_src ~breadcrumbs ~header ~config ~url ~sidebar title doc +end + +let render ~(config : Config.t) ~sidebar = function + (* .mld *) + | Document.Page page -> [ Page.page ~config ~sidebar page ] + (* .mli docs *) + | Source_page src -> [ Page.source_page ~config ~sidebar src ] + +let filepath ~config url = Link.Path.as_filename ~config url + +let doc ~config:_ ~xref_base_uri:_ _b = + (* let resolve = Link.Base xref_base_uri in + block ~config ~resolve b *) + Cmarkit.Doc.of_string ~layout:true ~strict:false "## Markdown" + +let inline ~config:_ ~xref_base_uri:_ _b = + (* let resolve = Link.Base xref_base_uri in + inline ~config ~resolve b *) + [] diff --git a/src/markdown2/generator.mli b/src/markdown2/generator.mli new file mode 100644 index 0000000000..afc3b57d6f --- /dev/null +++ b/src/markdown2/generator.mli @@ -0,0 +1,25 @@ +val render : + config:Config.t -> + sidebar:Odoc_document.Sidebar.t option -> + Odoc_document.Types.Document.t -> + Odoc_document.Renderer.page list + +val filepath : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t + +val items : + config:Config.t -> + resolve:Link.resolve -> + Odoc_document.Types.Item.t list -> + Cmarkit.Block.t list + +val doc : + config:Config.t -> + xref_base_uri:string -> + Odoc_document.Types.Block.t -> + Cmarkit.Doc.t + +val inline : + config:Config.t -> + xref_base_uri:string -> + Odoc_document.Types.Inline.t -> + Cmarkit.Inline.t list diff --git a/src/markdown2/link.ml b/src/markdown2/link.ml new file mode 100644 index 0000000000..f3c72bb559 --- /dev/null +++ b/src/markdown2/link.ml @@ -0,0 +1,125 @@ +module Url = Odoc_document.Url + +type link = Relative of string list * string | Absolute of string + +(* Translation from Url.Path *) +module Path = struct + let for_printing url = List.map snd @@ Url.Path.to_list url + + let segment_to_string (kind, name) = + Format.asprintf "%a%s" Url.Path.pp_disambiguating_prefix kind name + + let is_leaf_page url = url.Url.Path.kind = `LeafPage + + let remap _config f = + let l = String.concat "/" f in + let remaps = + [] + (* List.filter + (fun (prefix, _replacement) -> Astring.String.is_prefix ~affix:prefix l) + false (* (Config.remap config) *) *) + in + let remaps = + List.sort + (fun (a, _) (b, _) -> compare (String.length b) (String.length a)) + remaps + in + match remaps with + | [] -> None + | (prefix, replacement) :: _ -> + let len = String.length prefix in + let l = String.sub l len (String.length l - len) in + Some (replacement ^ l) + + let get_dir_and_file ~config:_ url = + let l = Url.Path.to_list url in + let is_dir = + if (* Config.flat config *) true then function + | `Page -> `Always | _ -> `Never + else function `LeafPage | `File | `SourcePage -> `Never | _ -> `Always + in + let dir, file = Url.Path.split ~is_dir l in + let dir = List.map segment_to_string dir in + let file = + match file with + | [] -> "index.html" + | [ (`LeafPage, name) ] -> name ^ ".html" + | [ (`File, name) ] -> name + | [ (`SourcePage, name) ] -> name ^ ".html" + | xs -> + (* assert (Config.flat config); *) + String.concat "-" (List.map segment_to_string xs) ^ ".html" + in + (dir, file) + + let for_linking ~config url = + let dir, file = get_dir_and_file ~config url in + match remap config dir with + | None -> Relative (dir, file) + | Some x -> Absolute (x ^ "/" ^ file) + + let as_filename ~config (url : Url.Path.t) = + let dir, file = get_dir_and_file ~config url in + Fpath.(v @@ String.concat Fpath.dir_sep (dir @ [ file ])) +end + +type resolve = Current of Url.Path.t | Base of string + +let rec drop_shared_prefix l1 l2 = + match (l1, l2) with + | l1 :: l1s, l2 :: l2s when l1 = l2 -> drop_shared_prefix l1s l2s + | _, _ -> (l1, l2) + +let href ~config ~resolve t = + let { Url.Anchor.page; anchor; _ } = t in + let add_anchor y = match anchor with "" -> y | anchor -> y ^ "#" ^ anchor in + let target_loc = Path.for_linking ~config page in + + match target_loc with + | Absolute y -> add_anchor y + | Relative (dir, file) -> ( + let target_loc = dir @ [ file ] in + (* If xref_base_uri is defined, do not perform relative URI resolution. *) + match resolve with + | Base xref_base_uri -> + let page = xref_base_uri ^ String.concat "/" target_loc in + add_anchor page + | Current path -> ( + let current_loc = + let dir, file = Path.get_dir_and_file ~config path in + dir @ [ file ] + in + + let current_from_common_ancestor, target_from_common_ancestor = + drop_shared_prefix current_loc target_loc + in + + let relative_target = + match current_from_common_ancestor with + | [] -> + (* We're already on the right page *) + (* If we're already on the right page, the target from our common + ancestor can't be anything other than the empty list *) + assert (target_from_common_ancestor = []); + [] + | [ _ ] -> + (* We're already in the right dir *) + target_from_common_ancestor + | l -> + (* We need to go up some dirs *) + List.map (fun _ -> "..") (List.tl l) + @ target_from_common_ancestor + in + let remove_index_html l = + match List.rev l with + | "index.html" :: rest -> List.rev ("" :: rest) + | _ -> l + in + let relative_target = + if (* Config.semantic_uris config *) true then + remove_index_html relative_target + else relative_target + in + match (relative_target, anchor) with + | [], "" -> "#" + | page, _ -> add_anchor @@ String.concat "/" page)) diff --git a/src/markdown2/link.mli b/src/markdown2/link.mli new file mode 100644 index 0000000000..3bff6dae3d --- /dev/null +++ b/src/markdown2/link.mli @@ -0,0 +1,15 @@ +(** HTML-specific interpretation of {!Odoc_document.Url} *) + +module Url = Odoc_document.Url + +type resolve = Current of Url.Path.t | Base of string + +val href : config:Config.t -> resolve:resolve -> Url.t -> string + +module Path : sig + val is_leaf_page : Url.Path.t -> bool + + val for_printing : Url.Path.t -> string list + + val as_filename : config:Config.t -> Url.Path.t -> Fpath.t +end diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml new file mode 100644 index 0000000000..ca63f1a835 --- /dev/null +++ b/src/markdown2/markdown_page.ml @@ -0,0 +1,269 @@ +(* + * Copyright (c) 2016 Thomas Refis + * + * Permission to use, copy, modify, and distribute this software for any + * purpose with or without fee is hereby granted, provided that the above + * copyright notice and this permission notice appear in all copies. + * + * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES + * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF + * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR + * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES + * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN + * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF + * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. + *) + +[@@@warning "-27-32"] + +open Odoc_utils + +module Url = Odoc_document.Url +module Html = Tyxml.Html + +let html_of_toc toc = + let open Types in + let rec section (section : toc) = + let link = Html.a ~a:[ Html.a_href section.href ] section.title in + match section.children with [] -> [ link ] | cs -> [ link; sections cs ] + and sections the_sections = + the_sections + |> List.map (fun the_section -> Html.li (section the_section)) + |> Html.ul + in + match toc with [] -> [] | _ -> [ sections toc ] + +let sidebars ~global_toc ~local_toc = + let local_toc = + match local_toc with + | [] -> [] + | _ :: _ -> + [ + Html.nav + ~a:[ Html.a_class [ "odoc-toc"; "odoc-local-toc" ] ] + (html_of_toc local_toc); + ] + in + let global_toc = + match global_toc with + | None -> [] + | Some c -> + [ Html.nav ~a:[ Html.a_class [ "odoc-toc"; "odoc-global-toc" ] ] c ] + in + match local_toc @ global_toc with + | [] -> [] + | tocs -> [ Html.div ~a:[ Html.a_class [ "odoc-tocs" ] ] tocs ] + +let html_of_breadcrumbs (breadcrumbs : Types.breadcrumbs) = + let make_navigation ~up_url rest = + let up = + match up_url with + | None -> [] + | Some up_url -> + [ Html.a ~a:[ Html.a_href up_url ] [ Html.txt "Up" ]; Html.txt " – " ] + in + [ Html.nav ~a:[ Html.a_class [ "odoc-nav" ] ] (up @ rest) ] + in + let space = Html.txt " " in + let sep = [ space; Html.entity "#x00BB"; space ] in + let html = + (* Create breadcrumbs *) + List.concat_map_sep ~sep + ~f:(fun (breadcrumb : Types.breadcrumb) -> + match breadcrumb.href with + | Some href -> + [ + [ + Html.a + ~a:[ Html.a_href href ] + (breadcrumb.name + :> Html_types.flow5_without_interactive Html.elt list); + ]; + ] + | None -> + [ (breadcrumb.name :> Html_types.nav_content_fun Html.elt list) ]) + breadcrumbs.parents + |> List.flatten + in + let current_name :> Html_types.nav_content_fun Html.elt list = + breadcrumbs.current.name + in + let rest = + if List.is_empty breadcrumbs.parents then current_name + else html @ sep @ current_name + in + make_navigation ~up_url:breadcrumbs.up_url + (rest :> [< Html_types.nav_content_fun > `A `PCDATA `Wbr ] Html.elt list) + +(* let file_uri ~config ~url (base : Types.uri) file = + match base with + | Types.Absolute uri -> uri ^ "/" ^ file + | Relative uri -> + let page = Url.Path.{ kind = `File; parent = uri; name = file } in + Link.href ~config ~resolve:(Current url) (Url.from_path page) + *) + +let page_creator ~config ~url ~uses_katex ~global_toc header breadcrumbs + local_toc content = + (* let theme_uri = None in + let support_uri = None in + let search_uris = [] in + let path = Link.Path.for_printing url in + + let head : Html_types.head Html.elt = + let title_string = + Printf.sprintf "%s (%s)" url.name (String.concat ~sep:"." path) + in + + let file_uri = file_uri ~config ~url in + let search_uri uri = + match uri with + | Types.Absolute uri -> uri + | Relative uri -> + Link.href ~config ~resolve:(Current url) (Url.from_path uri) + in + let search_scripts = + match search_uris with + | [] -> [] + | _ -> + let search_urls = List.map search_uri search_uris in + let search_urls = + let search_url name = Printf.sprintf "'%s'" name in + let search_urls = List.map search_url search_urls in + "[" ^ String.concat ~sep:"," search_urls ^ "]" + in + (* The names of the search scripts are put into a js variable. Then + the code in [odoc_search.js] load them into a webworker. *) + [ + Html.script ~a:[] + (Html.txt + (Format.asprintf + {|let base_url = '%s'; +let search_urls = %s; +|} + (let page = + Url.Path.{ kind = `File; parent = None; name = "" } + in + Link.href ~config ~resolve:(Current url) + (Url.from_path page)) + search_urls)); + Html.script + ~a: + [ + Html.a_src (file_uri support_uri "odoc_search.js"); + Html.a_defer (); + ] + (Html.txt ""); + ] + in + let meta_elements = + let highlightjs_meta = + let highlight_js_uri = file_uri support_uri "highlight.pack.js" in + [ + Html.script ~a:[ Html.a_src highlight_js_uri ] (Html.txt ""); + Html.script (Html.txt "hljs.initHighlightingOnLoad();"); + ] + in + let katex_meta = + if uses_katex then + let katex_css_uri = file_uri theme_uri "katex.min.css" in + let katex_js_uri = file_uri support_uri "katex.min.js" in + [ + Html.link ~rel:[ `Stylesheet ] ~href:katex_css_uri (); + Html.script ~a:[ Html.a_src katex_js_uri ] (Html.txt ""); + Html.script + (Html.cdata_script + {| + document.addEventListener("DOMContentLoaded", function () { + var elements = Array.from(document.getElementsByClassName("odoc-katex-math")); + for (var i = 0; i < elements.length; i++) { + var el = elements[i]; + var content = el.textContent; + var new_el = document.createElement("span"); + new_el.setAttribute("class", "odoc-katex-math-rendered"); + var display = el.classList.contains("display"); + katex.render(content, new_el, { throwOnError: false, displayMode: display }); + el.replaceWith(new_el); + } + }); + |}); + ] + else [] + in + default_meta_elements ~config ~url @ highlightjs_meta @ katex_meta + in + let meta_elements = meta_elements @ search_scripts in + Html.head (Html.title (Html.txt title_string)) meta_elements + in + let search_bar = + match search_uris with + | [] -> [] + | _ -> + [ Html.div ~a:[ Html.a_class [ "odoc-search" ] ] [ html_of_search () ] ] + in + + let body = + html_of_breadcrumbs breadcrumbs + @ search_bar + @ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ] + @ sidebars ~global_toc ~local_toc + @ [ Html.div ~a:[ Html.a_class [ "odoc-content" ] ] content ] + in + + let htmlpp = Html.pp () in + let html = Html.html head (Html.body ~a:[ Html.a_class [ "odoc" ] ] body) in + let content ppf = + htmlpp ppf html; + (* Tyxml's pp doesn't output a newline a the end, so we force one *) + Format.pp_force_newline ppf () + in + content *) + let content ppf = + let renderer = Cmarkit_commonmark.renderer () in + Format.printf "%s" (Cmarkit_renderer.doc_to_string renderer content) + in + content + +let make ~config ~url ~header ~breadcrumbs ~sidebar ~toc ~uses_katex content + children = + let filename = Link.Path.as_filename ~config url in + let content = + page_creator ~config ~url ~uses_katex ~global_toc:sidebar header breadcrumbs + toc content + in + { Odoc_document.Renderer.filename; content; children; path = url } + +let path_of_module_of_source ppf url = + match url.Url.Path.parent with + | Some parent -> + let path = Link.Path.for_printing parent in + Format.fprintf ppf " (%s)" (String.concat ~sep:"." path) + | None -> () + +let src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar name content = + (* let head : Html_types.head Html.elt = + let title_string = + Format.asprintf "Source: %s%a" name path_of_module_of_source url + in + let meta_elements = [] in + Html.head (Html.title (Html.txt title_string)) meta_elements + in + let body = + html_of_breadcrumbs breadcrumbs + @ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ] + @ sidebars ~global_toc:sidebar ~local_toc:[] + @ content + in *) + let content ppf = + Format.fprintf ppf "%s" "TODO!"; + (* Tyxml's pp doesn't output a newline a the end, so we force one *) + Format.pp_force_newline ppf () + in + content + +let make_src ~config ~url ~breadcrumbs ~header ~sidebar title content = + let filename = Link.Path.as_filename ~config url in + let content = + src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar title content + in + { Odoc_document.Renderer.filename; content; children = []; path = url } diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli new file mode 100644 index 0000000000..f18633e11b --- /dev/null +++ b/src/markdown2/markdown_page.mli @@ -0,0 +1,47 @@ +(* + * Copyright (c) 2016 Thomas Refis + * + * Permission to use, copy, modify, and distribute this software for any + * purpose with or without fee is hereby granted, provided that the above + * copyright notice and this permission notice appear in all copies. + * + * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES + * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF + * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR + * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES + * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN + * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF + * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. + *) + +(** Supported languages for printing code parts. *) + +(** {1 Page creator} *) + +val make : + config:Config.t -> + url:Odoc_document.Url.Path.t -> + header:Cmarkit.Block.t list -> + breadcrumbs:Types.breadcrumbs -> + sidebar:Cmarkit.Block.t list option -> + toc:Types.toc list -> + uses_katex:bool -> + Cmarkit.Doc.t -> + Odoc_document.Renderer.page list -> + Odoc_document.Renderer.page +(** [make ?theme_uri (body, children)] calls "the page creator" to turn [body] + into an [[ `Html ] elt]. If [theme_uri] is provided, it will be used to + locate the theme files, otherwise the HTML output directory is used. *) + +val make_src : + config:Config.t -> + url:Odoc_document.Url.Path.t -> + breadcrumbs:Types.breadcrumbs -> + header:Cmarkit.Block.t list -> + sidebar:Cmarkit.Block.t list option -> + string -> + Cmarkit.Block.t list -> + Odoc_document.Renderer.page +(** [make ?theme_uri (body, children)] calls "the page creator" to turn [body] + into an [[ `Html ] elt]. If [theme_uri] is provided, it will be used to + locate the theme files, otherwise the HTML output directory is used. *) diff --git a/src/markdown2/markdown_source.ml b/src/markdown2/markdown_source.ml new file mode 100644 index 0000000000..de5257e57e --- /dev/null +++ b/src/markdown2/markdown_source.ml @@ -0,0 +1,81 @@ +open Odoc_utils +module HLink = Link +open Odoc_document.Types +open Tyxml +module Link = HLink + +let html_of_doc ~config ~resolve docs = + let open Html in + let a : + ( [< Html_types.a_attrib ], + [< Html_types.span_content_fun ], + [> Html_types.span ] ) + star = + Unsafe.node "a" + (* Makes it possible to use inside span. Although this is not standard (see + https://developer.mozilla.org/en-US/docs/Web/Guide/HTML/Content_categories) + it is validated by the {{:https://validator.w3.org/nu/#textarea}W3C}. *) + in + (* [a] tags should not contain in other [a] tags. If this happens, browsers + start to be really weird. If PPX do bad things, such a situation could + happen. We manually avoid this situation. *) + let rec doc_to_html ~is_in_a doc = + match doc with + | Source_page.Plain_code s -> [ txt s ] + | Tagged_code (info, docs) -> ( + let is_in_a = match info with Link _ -> true | _ -> is_in_a in + let children = List.concat_map (doc_to_html ~is_in_a) docs in + match info with + | Syntax tok -> [ span ~a:[ a_class [ tok ] ] children ] + (* Currently, we do not render links to documentation *) + | Link { documentation = _; implementation = None } -> children + | Link { documentation = _; implementation = Some anchor } -> + let href = Link.href ~config ~resolve anchor in + [ a ~a:[ a_href href ] children ] + | Anchor lbl -> [ span ~a:[ a_id lbl ] children ]) + in + let span_content = List.concat_map (doc_to_html ~is_in_a:false) docs in + span ~a:[] span_content + +let count_lines_in_string s = + let n = ref 0 in + String.iter (function '\n' -> incr n | _ -> ()) s; + !n + +(** Traverse the doc to count the number of lines. *) +let rec count_lines_in_span = function + | Source_page.Plain_code s -> count_lines_in_string s + | Tagged_code (_, docs) -> count_lines docs + +and count_lines l = + let rec inner l acc = + match l with + | [] -> acc + | hd :: tl -> inner tl (count_lines_in_span hd + acc) + in + inner l 0 + +let rec line_numbers acc n = + let open Html in + if n < 1 then acc + else + let l = string_of_int n in + let anchor = + a + ~a:[ a_id ("L" ^ l); a_class [ "source_line" ]; a_href ("#L" ^ l) ] + [ txt l ] + in + line_numbers (anchor :: txt "\n" :: acc) (n - 1) + +let html_of_doc ~config ~resolve docs = + let open Html in + pre + ~a:[ a_class [ "source_container" ] ] + [ + code + ~a:[ a_class [ "source_line_column" ] ] + (line_numbers [] (count_lines docs)); + code + ~a:[ a_class [ "source_code" ] ] + [ html_of_doc ~config ~resolve docs ]; + ] diff --git a/src/markdown2/markdown_source.mli b/src/markdown2/markdown_source.mli new file mode 100644 index 0000000000..1e09f4bd61 --- /dev/null +++ b/src/markdown2/markdown_source.mli @@ -0,0 +1,5 @@ +val html_of_doc : + config:Config.t -> + resolve:Link.resolve -> + Odoc_document.Types.Source_page.code -> + [> Html_types.pre ] Tyxml.Html.elt diff --git a/src/markdown2/odoc_markdown.ml b/src/markdown2/odoc_markdown.ml new file mode 100644 index 0000000000..63facdde9e --- /dev/null +++ b/src/markdown2/odoc_markdown.ml @@ -0,0 +1,10 @@ +module Types = Types +module Config = Config + +module Markdown_page = Markdown_page +(** @canonical Odoc_html.Html_page *) + +module Generator = Generator +module Link = Link +module Json = Odoc_utils.Json +module Sidebar = Sidebar diff --git a/src/markdown2/sidebar.ml b/src/markdown2/sidebar.ml new file mode 100644 index 0000000000..59996fee2f --- /dev/null +++ b/src/markdown2/sidebar.ml @@ -0,0 +1,25 @@ +open Odoc_utils + +let toc_to_json + ({ url; valid_link; content = _; _ } : Odoc_document.Sidebar.entry) : + Json.json = + (* let config = + Config.v ~semantic_uris:true ~indent:true ~flat:false ~open_details:false + ~as_json:true ~remap:[] () + in *) + let url, kind = + match valid_link with + | false -> (`Null, `Null) + | true -> + let _href = Link.href ~resolve:(Link.Base "") url in + let kind = + Format.asprintf "%a" Odoc_document.Url.Anchor.pp_kind url.kind + in + + (`String "TODO", `String kind) + in + let inline = `String "TODO" in + `Object [ ("url", url); ("kind", kind); ("content", inline) ] + +let to_json (sidebar : Odoc_document.Sidebar.t) = + `Array (List.map (Tree.to_json toc_to_json) sidebar) diff --git a/src/markdown2/sidebar.mli b/src/markdown2/sidebar.mli new file mode 100644 index 0000000000..77458ad0f3 --- /dev/null +++ b/src/markdown2/sidebar.mli @@ -0,0 +1 @@ +val to_json : Odoc_document.Sidebar.t -> Odoc_utils.Json.json diff --git a/src/markdown2/types.ml b/src/markdown2/types.ml new file mode 100644 index 0000000000..73699470f6 --- /dev/null +++ b/src/markdown2/types.ml @@ -0,0 +1,24 @@ +(* Type definitions for the HTML renderer *) + +type uri = Absolute of string | Relative of Odoc_document.Url.Path.t option + +type file_uri = Absolute of string | Relative of Odoc_document.Url.Path.t + +type toc = { + title : Html_types.flow5_without_interactive Tyxml.Html.elt list; + title_str : string; + href : string; + children : toc list; +} + +type breadcrumb = { + href : string option; + name : Html_types.phrasing_without_interactive Tyxml.Html.elt list; + kind : Odoc_document.Url.Path.kind; +} + +type breadcrumbs = { + parents : breadcrumb list; + current : breadcrumb; + up_url : string option; +} From b7ed9f5e94941174cc7d6cfb7362ea417473930a Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 7 Mar 2025 13:37:02 +0100 Subject: [PATCH 03/53] Enable odoc_markdown in the cli --- src/odoc/bin/main.ml | 15 +++++++++++++++ src/odoc/dune | 1 + 2 files changed, 16 insertions(+) diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index eea2b62cdc..8e9f8fa452 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1312,6 +1312,19 @@ end module Odoc_html = Make_renderer (Odoc_html_args) +module Odoc_markdown_cmd = Make_renderer (struct + type args = Odoc_markdown.Config.t + + let render config sidebar page = + Odoc_markdown.Generator.render ~config ~sidebar page + + let filepath _url = failwith "Not implemented" + (* Odoc_html.Generator.filepath ~config:html_config url *) + + let extra_args = Term.const { Odoc_markdown.Config.root_url = None } + let renderer = { Odoc_document.Renderer.name = "markdown"; render; filepath } +end) + module Odoc_html_url : sig val cmd : unit Term.t @@ -1708,6 +1721,8 @@ let () = Odoc_link.(cmd, info ~docs:section_pipeline); Odoc_html.generate ~docs:section_pipeline; Odoc_html.generate_source ~docs:section_pipeline; + Odoc_markdown_cmd.generate ~docs:section_pipeline; + (* Odoc_markdown_cmd.generate_source ~docs:section_pipeline; *) Odoc_html.generate_asset ~docs:section_pipeline; Support_files_command.(cmd, info ~docs:section_pipeline); Compile_impl.(cmd, info ~docs:section_pipeline); diff --git a/src/odoc/dune b/src/odoc/dune index 6cf692f2ed..a91e231962 100644 --- a/src/odoc/dune +++ b/src/odoc/dune @@ -5,6 +5,7 @@ compiler-libs.common fpath odoc_html + odoc_markdown odoc_html_support_files odoc_latex odoc_loader From fad39e0323432b968bb969ee94ecb35600fa2a27 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 7 Mar 2025 18:35:02 +0100 Subject: [PATCH 04/53] We have titles working in markdown --- src/markdown2/generator.ml | 202 ++++++++++++-------------- test/integration/markdown.t/run.t | 4 +- test/integration/markdown.t/test.mli | 1 - test/integration/markdown.t/test2.mli | 2 - 4 files changed, 96 insertions(+), 113 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 3d785f52c8..080a309b75 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -15,6 +15,7 @@ *) [@@@warning "-32-26-27"] +[@@@warning "-39"] (* rec flag *) open Odoc_utils @@ -24,17 +25,12 @@ module Html = Tyxml.Html module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url module Link = HLink -module Blocks = Cmarkit.Block -type any = Html_types.flow5 - -type item = Html_types.flow5_without_header_footer - -type flow = Html_types.flow5_without_sectioning_heading_header_footer - -type phrasing = Html_types.phrasing - -type non_link_phrasing = Html_types.phrasing_without_interactive +module Md = struct + module Block = Cmarkit.Block + module Inline = Cmarkit.Inline + let meta = Cmarkit.Meta.none +end let mk_anchor_link id = [ Html.a ~a:[ Html.a_href ("#" ^ id); Html.a_class [ "anchor" ] ] [] ] @@ -78,16 +74,22 @@ and raw_markup (t : Raw_markup.t) = [ Html.Unsafe.data content ] | _ -> [] -and source k ?a (t : Source.t) = +and source (k : Inline.one list -> Md.Inline.t list) ?a (t : Source.t) = let rec token (x : Source.token) = match x with | Elt i -> k i | Tag (None, l) -> let content = tokens l in - if content = [] then [] else [ Html.span content ] - | Tag (Some s, l) -> [ Html.span ~a:[ Html.a_class [ s ] ] (tokens l) ] + if content = [] then [] + else + (* TODO: extract content, lang?, ??? *) + let heading_1_inline = Md.Inline.Text ("Heading 1", Md.meta) in + [ heading_1_inline ] + | Tag (Some s, l) -> + (* [ Html.span ~a:[ Html.a_class [ s ] ] (tokens l) ] *) + failwith "source not implemented tag Some" and tokens t = List.concat_map token t in - match tokens t with [] -> [] | l -> [ Html.code ?a l ] + match tokens t with [] -> [] | l -> l and styled style ~emph_level = match style with @@ -104,7 +106,7 @@ let rec internallink ~config ~emph_level ~resolve ?(a = []) target content let a = match tooltip with Some s -> Html.a_title s :: a | None -> a in let elt = match target with - | Target.Resolved uri -> + (* | Target.Resolved uri -> let href = Link.href ~config ~resolve uri in let content = inline_nolink ~emph_level content in @@ -118,41 +120,46 @@ let rec internallink ~config ~emph_level ~resolve ?(a = []) target content * (ref_to_string ref) * in *) let a = Html.a_class [ "xref-unresolved" ] :: a in - Html.span ~a (inline ~config ~emph_level ~resolve content) + Html.span ~a (inline ~config ~emph_level ~resolve content) *) + | _ -> failwith "internallink not implemented" in - [ (elt :> phrasing Html.elt) ] + [ elt ] -and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : - phrasing Html.elt list = - let one (t : Inline.one) = - let a = class_ t.attr in +and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : Md.Inline.t list + = + let one (t : Inline.one) : Md.Inline.t list = match t.desc with - | Text "" -> [] | Text s -> - if a = [] then [ Html.txt s ] else [ Html.span ~a [ Html.txt s ] ] + let inline = Md.Inline.Text (s, Md.meta) in + [ inline ] | Entity s -> - if a = [] then [ Html.entity s ] else [ Html.span ~a [ Html.entity s ] ] - | Linebreak -> [ Html.br ~a () ] + failwith "inline not implemented entity" + (* if a = [] then [ Html.entity s ] else [ Html.span ~a [ Html.entity s ] ] *) + | Linebreak -> failwith "inline not implemented linebreak" | Styled (style, c) -> - let emph_level, app_style = styled style ~emph_level in - [ app_style @@ inline ~config ~emph_level ~resolve c ] + failwith "inline not implemented styled" + (* let emph_level, app_style = styled style ~emph_level in + [ app_style @@ inline ~config ~emph_level ~resolve c ] *) | Link { target = External href; content = c; _ } -> - let a = (a :> Html_types.a_attrib Html.attrib list) in + failwith "inline not implemented ext link" + (* let a = (a :> Html_types.a_attrib Html.attrib list) in let content = inline_nolink ~emph_level c in - [ Html.a ~a:(Html.a_href href :: a) content ] + [ Html.a ~a:(Html.a_href href :: a) content ] *) | Link { target = Internal t; content; tooltip } -> - internallink ~config ~emph_level ~resolve ~a t content tooltip - | Source c -> source (inline ~config ~emph_level ~resolve) ~a c - | Math s -> [ inline_math s ] - | Raw_markup r -> raw_markup r + failwith "inline not implemented inline link" + (* internallink ~config ~emph_level ~resolve ~a t content tooltip *) + | Source c -> source (inline ~config ~emph_level ~resolve) c + | Math s -> (* [ inline_math s ] *) failwith "inline not implemented math" + | Raw_markup r -> + (* raw_markup r *) + failwith "inline not implemented markup!" in List.concat_map one l -and inline_nolink ?(emph_level = 0) (l : Inline.t) : - non_link_phrasing Html.elt list = +and inline_nolink ?(emph_level = 0) (l : Inline.t) : Md.Block.t list = let one (t : Inline.one) = - let a = class_ t.attr in - match t.desc with + failwith "inline_nolink not implemented" + (* match t.desc with | Text "" -> [] | Text s -> if a = [] then [ Html.txt s ] else [ Html.span ~a [ Html.txt s ] ] @@ -165,28 +172,18 @@ and inline_nolink ?(emph_level = 0) (l : Inline.t) : | Link _ -> assert false | Source c -> source (inline_nolink ~emph_level) ~a c | Math s -> [ inline_math s ] - | Raw_markup r -> raw_markup r + | Raw_markup r -> raw_markup r *) in List.concat_map one l -let heading ~config ~resolve (h : Heading.t) = - let a, anchor = - match h.label with - | Some id -> ([ Html.a_id id ], mk_anchor_link id) - | None -> ([], []) +let heading ~config ~resolve (h : Heading.t) : Md.Block.t list = + let id = h.label in + let inlines = inline ~config ~resolve h.title in + let content = Md.Inline.Inlines (inlines, Md.meta) in + let heading = + Md.Block.Heading (Md.Block.Heading.make ~level:h.level content, Md.meta) in - let content = inline ~config ~resolve h.title in - let source_link = mk_link_to_source ~config ~resolve h.source_anchor in - let mk = - match h.level with - | 0 -> Html.h1 - | 1 -> Html.h2 - | 2 -> Html.h3 - | 3 -> Html.h4 - | 4 -> Html.h5 - | _ -> Html.h6 - in - mk ~a (anchor @ content @ source_link) + [ heading ] let text_align = function | Table.Left -> [ Html.a_style "text-align:left" ] @@ -196,10 +193,9 @@ let text_align = function 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) = - let mk_block ?(extra_class = []) mk content = +let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = + let one (t : Block.one) : Md.Block.t list = + (* let mk_block ?(extra_class = []) mk content = let a = Some (class_ (extra_class @ t.attr)) in [ mk ?a content ] in @@ -216,8 +212,17 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list = [ Html.span ~a content ] in mk_block Html.div block - in + in *) match t.desc with + | Paragraph paragraph -> + let inlines = inline ~config ~resolve paragraph in + let inlines = Md.Inline.Inlines (inlines, Md.meta) in + let paragraph_block = + Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) + in + [ paragraph_block ] + | _ -> failwith "block not implemented" + (* match t.desc with | Inline i -> if t.attr = [] then as_flow @@ inline ~config ~resolve i else mk_block Html.span (inline ~config ~resolve i) @@ -274,13 +279,12 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list = in [ img ] in - mk_media_block image target alt + mk_media_block image target alt *) in - List.concat_map one l -and mk_rows ~config ~resolve { align; data } = - let mk_row row = +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) @@ -300,27 +304,22 @@ and mk_rows ~config ~resolve { align; data } = in Html.tr (List.rev acc) in - List.map mk_row data + List.map mk_row data *) + failwith "notimpemented" (* 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 *) -let flow_to_item : flow Html.elt list -> item Html.elt list = - fun x -> Html.totl @@ Html.toeltl x - -let div : (Html_types.div_attrib, [< item ], [> Html_types.div ]) Html.star = - Html.Unsafe.node "div" - -let spec_class attr = class_ ("spec" :: attr) let spec_doc_div ~config ~resolve = function | [] -> [] | docs -> - let a = [ Html.a_class [ "spec-doc" ] ] in - [ div ~a (flow_to_item @@ block ~config ~resolve docs) ] + (* let a = [ Html.a_class [ "spec-doc" ] ] in + [ div ~a (flow_to_item @@ block ~config ~resolve docs) ] *) + [] -let rec documentedSrc ~config ~resolve (t : DocumentedSrc.t) : +(* let rec documentedSrc ~config ~resolve (t : DocumentedSrc.t) : item Html.elt list = let open DocumentedSrc in let take_code l = @@ -375,15 +374,13 @@ let rec documentedSrc ~config ~resolve (t : DocumentedSrc.t) : in Html.ol (List.map one l) :: to_html rest in - to_html t + to_html t *) and subpage ~config:_ ~resolve:_ (_subp : Subpage.t) = (* items ~config ~resolve subp.content.items *) [] -(* I will be right back *) - -and items ~config ~resolve l : Blocks.t list = +and items ~config ~resolve l : Md.Block.t list = let rec walk_items acc (t : Item.t list) = let continue_with rest elts = (walk_items [@tailcall]) (List.rev_append elts acc) rest @@ -396,16 +393,10 @@ and items ~config ~resolve l : Blocks.t list = | Item.Text text -> Accum text | _ -> Stop_and_keep) in - (* let content = flow_to_item @@ block ~config ~resolve text in *) - (* let inline = Cmarkit.Inline.(Text "asdf") in *) - (* let text = Cmarkit.Inline.text "This is paragraph text" in - let inline = Cmarkit.Inline.of_text text in - let content = Cmarkit.Block.paragraph inline in *) - let content = [ Blocks.empty ] in + let content = block ~config ~resolve text in (continue_with [@tailcall]) rest content | Heading h :: rest -> - let headings = [ Blocks.empty ] in - (continue_with [@tailcall]) rest headings + (continue_with [@tailcall]) rest (heading ~config ~resolve h) | Include { attr; @@ -415,13 +406,13 @@ and items ~config ~resolve l : Blocks.t list = content = { summary; status; content }; } :: rest -> - let doc = spec_doc_div ~config ~resolve doc in + (* let doc = spec_doc_div ~config ~resolve doc in let included_html = items content in let a_class = if List.length content = 0 then [ "odoc-include"; "shadowed-include" ] else [ "odoc-include" ] - in - let content = [ Blocks.empty ] in + in *) + let content = [ Md.Block.empty ] in (* let content = let details ~open' = let open' = if open' then [ Html.a_open () ] else [] in @@ -450,13 +441,13 @@ and items ~config ~resolve l : Blocks.t list = in *) (continue_with [@tailcall]) rest content | Declaration { Item.attr; anchor; source_anchor; content; doc } :: rest -> - let extra_attr, extra_class, anchor_link = mk_anchor anchor in + (* let extra_attr, extra_class, anchor_link = mk_anchor anchor in let link_to_source = mk_link_to_source ~config ~resolve source_anchor in let a = spec_class (attr @ extra_class) @ extra_attr in let content = anchor_link @ link_to_source @ documentedSrc ~config ~resolve content - in - let spec = [ Blocks.empty ] in + in *) + let spec = [ Md.Block.empty ] in (* let spec = let doc = spec_doc_div ~config ~resolve doc in [ div ~a:[ Html.a_class [ "odoc-spec" ] ] (div ~a content :: doc) ] @@ -476,16 +467,12 @@ module Toc = struct let gen_toc ~config ~resolve ~path i = let toc = Toc.compute path ~on_sub i in let rec section { Toc.url; text; children } = - let text = inline_nolink text in + (* let text = inline_nolink text in *) let title = - (text - : non_link_phrasing Html.elt list - :> Html_types.flow5_without_interactive Html.elt list) - in - let title_str = - List.map (Format.asprintf "%a" (Tyxml.Html.pp_elt ())) text - |> String.concat ~sep:"" + (* (text) *) + [] in + let title_str = "" in let href = Link.href ~config ~resolve url in { title; title_str; href; children = List.map section children } in @@ -587,7 +574,8 @@ module Breadcrumbs = struct Some (Link.href ~config ~resolve:(Current current_url) url) else None in - let name = inline_nolink content in + (* let name = inline_nolink content in *) + let name = [] in let breadcrumb = { href; name; kind = url.page.kind } in if url.page = current_url then Some (`Current breadcrumb) else Some (`Parent (breadcrumb, children)) @@ -651,15 +639,13 @@ module Page = struct let uses_katex = Doctree.Math.has_math_elements p in let toc = Toc.gen_toc ~config ~resolve ~path:url i in let content = items ~config ~resolve i in - let content = - (* Cmarkit.Doc.empty *) - Cmarkit.Doc.of_string ~layout:true ~strict:false "## Markdown" - in + let root_block = Md.Block.Blocks (content, Md.meta) in + let doc = Cmarkit.Doc.make root_block in let header, preamble = Doctree.PageTitle.render_title ?source_anchor p in let header = items ~config ~resolve header in let preamble = items ~config ~resolve preamble in Markdown_page.make ~sidebar ~config ~header:(header @ preamble) ~toc - ~breadcrumbs ~url ~uses_katex content subpages + ~breadcrumbs ~url ~uses_katex doc subpages and source_page ~config ~sidebar sp = let { Source_page.url; contents } = sp in @@ -673,7 +659,7 @@ module Page = struct (Some (block ~config ~resolve sidebar) :> any Html.elt list option) *) None in - let title = url.Url.Path.name and doc = [ Blocks.empty ] in + let title = url.Url.Path.name and doc = [ Md.Block.empty ] in (* and doc = Markdown_source.html_of_doc ~config ~resolve contents in *) let header = (* items ~config ~resolve (Doctree.PageTitle.render_src_title sp) *) diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index f9d3e114b8..307e4cf526 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -1,6 +1,6 @@ $ ocamlc -c -bin-annot test.mli $ ocamlc -c -bin-annot test2.mli - $ printf "{0 The title}\n" > page.mld + $ printf "{0 The title}\n something else" > page.mld $ odoc compile --package test test.cmti $ odoc compile --package test -I . test2.cmti $ odoc compile --package test -I . page.mld @@ -8,4 +8,4 @@ $ odoc link test2.odoc $ odoc link page-page.odoc $ odoc markdown-generate test.odocl -o markdown - $ ls markdown + $ cat markdown/test/Test.html diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli index 081a2c018f..4bc52ea372 100644 --- a/test/integration/markdown.t/test.mli +++ b/test/integration/markdown.t/test.mli @@ -7,4 +7,3 @@ type t (** {1 Section 2} *) type u - diff --git a/test/integration/markdown.t/test2.mli b/test/integration/markdown.t/test2.mli index dfbac3c757..c3ac1bf713 100644 --- a/test/integration/markdown.t/test2.mli +++ b/test/integration/markdown.t/test2.mli @@ -1,3 +1 @@ val v : Test.t - - From 62c5a116c9ee1bdbb376418a517db4b8401df9f2 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 7 Mar 2025 19:27:59 +0100 Subject: [PATCH 05/53] Fix inlines --- src/markdown2/generator.ml | 41 +++++++++----------------------------- 1 file changed, 9 insertions(+), 32 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 080a309b75..16af8915bf 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -15,7 +15,6 @@ *) [@@@warning "-32-26-27"] -[@@@warning "-39"] (* rec flag *) open Odoc_utils @@ -80,16 +79,12 @@ and source (k : Inline.one list -> Md.Inline.t list) ?a (t : Source.t) = | Elt i -> k i | Tag (None, l) -> let content = tokens l in - if content = [] then [] - else - (* TODO: extract content, lang?, ??? *) - let heading_1_inline = Md.Inline.Text ("Heading 1", Md.meta) in - [ heading_1_inline ] + content | Tag (Some s, l) -> (* [ Html.span ~a:[ Html.a_class [ s ] ] (tokens l) ] *) failwith "source not implemented tag Some" and tokens t = List.concat_map token t in - match tokens t with [] -> [] | l -> l + tokens t and styled style ~emph_level = match style with @@ -108,7 +103,7 @@ let rec internallink ~config ~emph_level ~resolve ?(a = []) target content match target with (* | Target.Resolved uri -> let href = Link.href ~config ~resolve uri in - let content = inline_nolink ~emph_level content in + let content = inline ~emph_level content in let a = Html.a_href href :: (a :> Html_types.a_attrib Html.attrib list) @@ -143,7 +138,7 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : Md.Inline.t list | Link { target = External href; content = c; _ } -> failwith "inline not implemented ext link" (* let a = (a :> Html_types.a_attrib Html.attrib list) in - let content = inline_nolink ~emph_level c in + let content = inline ~emph_level c in [ Html.a ~a:(Html.a_href href :: a) content ] *) | Link { target = Internal t; content; tooltip } -> failwith "inline not implemented inline link" @@ -156,26 +151,6 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : Md.Inline.t list in List.concat_map one l -and inline_nolink ?(emph_level = 0) (l : Inline.t) : Md.Block.t list = - let one (t : Inline.one) = - failwith "inline_nolink not implemented" - (* match t.desc with - | Text "" -> [] - | Text s -> - if a = [] then [ Html.txt s ] else [ Html.span ~a [ Html.txt s ] ] - | Entity s -> - if a = [] then [ Html.entity s ] else [ Html.span ~a [ Html.entity s ] ] - | Linebreak -> [ Html.br ~a () ] - | Styled (style, c) -> - let emph_level, app_style = styled style ~emph_level in - [ app_style @@ inline_nolink ~emph_level c ] - | Link _ -> assert false - | Source c -> source (inline_nolink ~emph_level) ~a c - | Math s -> [ inline_math s ] - | Raw_markup r -> raw_markup r *) - in - List.concat_map one l - let heading ~config ~resolve (h : Heading.t) : Md.Block.t list = let id = h.label in let inlines = inline ~config ~resolve h.title in @@ -193,6 +168,8 @@ let text_align = function let cell_kind = function `Header -> Html.th | `Data -> Html.td +[@@@warning "-39"] + let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = let one (t : Block.one) : Md.Block.t list = (* let mk_block ?(extra_class = []) mk content = @@ -447,7 +424,7 @@ and items ~config ~resolve l : Md.Block.t list = let content = anchor_link @ link_to_source @ documentedSrc ~config ~resolve content in *) - let spec = [ Md.Block.empty ] in + let spec = block ~config ~resolve doc in (* let spec = let doc = spec_doc_div ~config ~resolve doc in [ div ~a:[ Html.a_class [ "odoc-spec" ] ] (div ~a content :: doc) ] @@ -467,7 +444,7 @@ module Toc = struct let gen_toc ~config ~resolve ~path i = let toc = Toc.compute path ~on_sub i in let rec section { Toc.url; text; children } = - (* let text = inline_nolink text in *) + let text = inline ~config ~resolve text in let title = (* (text) *) [] @@ -574,7 +551,7 @@ module Breadcrumbs = struct Some (Link.href ~config ~resolve:(Current current_url) url) else None in - (* let name = inline_nolink content in *) + (* let name = inline content in *) let name = [] in let breadcrumb = { href; name; kind = url.page.kind } in if url.page = current_url then Some (`Current breadcrumb) From 839c8c22e80c280721b722b3e94a7a091f828e21 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Tue, 18 Mar 2025 10:50:42 +0100 Subject: [PATCH 06/53] Most of the blocks minimally supported --- src/markdown2/generator.ml | 655 ++++++++++++++------------- test/integration/markdown.t/run.t | 59 +++ test/integration/markdown.t/test.mli | 308 ++++++++++++- 3 files changed, 706 insertions(+), 316 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 16af8915bf..c970642de6 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -14,182 +14,142 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -[@@@warning "-32-26-27"] - open Odoc_utils module HLink = Link open Odoc_document.Types -module Html = Tyxml.Html module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url module Link = HLink module Md = struct - module Block = Cmarkit.Block - module Inline = Cmarkit.Inline + include Cmarkit + let meta = Cmarkit.Meta.none end -let mk_anchor_link id = - [ Html.a ~a:[ Html.a_href ("#" ^ id); Html.a_class [ "anchor" ] ] [] ] - -let mk_anchor anchor = - match anchor with - | None -> ([], [], []) - | Some { Url.Anchor.anchor; _ } -> - let link = mk_anchor_link anchor in - let extra_attr = [ Html.a_id anchor ] in - let extra_class = [ "anchored" ] in - (extra_attr, extra_class, link) - -let mk_link_to_source ~config ~resolve anchor = - match anchor with - | None -> [] - | Some url -> - let href = Link.href ~config ~resolve url in - [ - Html.a - ~a:[ Html.a_href href; Html.a_class [ "source_link" ] ] - [ Html.txt "Source" ]; - ] - -let class_ (l : Class.t) = if l = [] then [] else [ Html.a_class l ] - -let inline_math (s : Math.t) = - Html.code ~a:[ Html.a_class [ "odoc-katex-math" ] ] [ Html.txt s ] - -let block_math (s : Math.t) = - Html.pre ~a:[ Html.a_class [ "odoc-katex-math"; "display" ] ] [ Html.txt s ] - -and raw_markup (t : Raw_markup.t) = - let target, content = t in - match Astring.String.Ascii.lowercase target with - | "html" -> - (* This is OK because we output *textual* HTML. - In theory, we should try to parse the HTML with lambdasoup and rebuild - the HTML tree from there. - *) - [ Html.Unsafe.data content ] - | _ -> [] - -and source (k : Inline.one list -> Md.Inline.t list) ?a (t : Source.t) = +let source k (t : Source.t) = let rec token (x : Source.token) = match x with | Elt i -> k i - | Tag (None, l) -> - let content = tokens l in - content - | Tag (Some s, l) -> - (* [ Html.span ~a:[ Html.a_class [ s ] ] (tokens l) ] *) - failwith "source not implemented tag Some" + | Tag (None, l) -> tokens l + | Tag (Some _s, l) -> + (* TODO: Implement tag with Some, what's the difference between Some and None? *) + tokens l and tokens t = List.concat_map token t in tokens t -and styled style ~emph_level = +(* TODO: What's emph_level? *) +and styled style ~emph_level:_ content = match style with - | `Emphasis -> - let a = if emph_level mod 2 = 0 then [] else [ Html.a_class [ "odd" ] ] in - (emph_level + 1, Html.em ~a) - | `Bold -> (emph_level, Html.b ~a:[]) - | `Italic -> (emph_level, Html.i ~a:[]) - | `Superscript -> (emph_level, Html.sup ~a:[]) - | `Subscript -> (emph_level, Html.sub ~a:[]) - -let rec internallink ~config ~emph_level ~resolve ?(a = []) target content - tooltip = - let a = match tooltip with Some s -> Html.a_title s :: a | None -> a in - let elt = - match target with - (* | Target.Resolved uri -> - let href = Link.href ~config ~resolve uri in - let content = inline ~emph_level content in - - let a = - Html.a_href href :: (a :> Html_types.a_attrib Html.attrib list) - in - Html.a ~a content - | Unresolved -> - (* let title = - * Html.a_title (Printf.sprintf "unresolved reference to %S" - * (ref_to_string ref) - * in *) - let a = Html.a_class [ "xref-unresolved" ] :: a in - Html.span ~a (inline ~config ~emph_level ~resolve content) *) - | _ -> failwith "internallink not implemented" - in - [ elt ] - -and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : Md.Inline.t list - = - let one (t : Inline.one) : Md.Inline.t list = + | `Bold -> + let inlines_as_one_inline = Md.Inline.Inlines (content, Md.meta) in + let emphasis = Md.Inline.Emphasis.make inlines_as_one_inline in + [ Md.Inline.Strong_emphasis (emphasis, Md.meta) ] + | `Italic | `Emphasis -> + (* We treat emphasis as italic, since there's no difference in Markdown *) + let inlines_as_one_inline = Md.Inline.Inlines (content, Md.meta) in + let emphasis = Md.Inline.Emphasis.make inlines_as_one_inline in + [ Md.Inline.Emphasis (emphasis, Md.meta) ] + | `Superscript | `Subscript -> + (* CommonMark doesn't have native support for superscript/subscript, + so we just include the content as inline directly *) + content + +let rec inline_text_only (inline : Inline.t) : string list = + List.concat_map + (fun (i : Inline.one) -> + match i.desc with + | Text s -> [ s ] + | Entity s -> [ s ] + | Styled (_, content) -> inline_text_only content + | Link { content; _ } -> inline_text_only content + | Source s -> source inline_text_only s + | _ -> []) + inline + +and block_text_only (blocks : Block.t) : string list = + List.concat_map + (fun (b : Block.one) -> + match b.desc with + | Paragraph inline | Inline inline -> inline_text_only inline + | Source (_, s) -> source inline_text_only s + | List (_, items) -> List.concat_map block_text_only items + | Verbatim s -> [ s ] + | _ -> []) + blocks + +and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = + let one (t : Inline.one) = match t.desc with - | Text s -> - let inline = Md.Inline.Text (s, Md.meta) in - [ inline ] + | Text s -> [ Md.Inline.Text (s, Md.meta) ] | Entity s -> - failwith "inline not implemented entity" - (* if a = [] then [ Html.entity s ] else [ Html.span ~a [ Html.entity s ] ] *) - | Linebreak -> failwith "inline not implemented linebreak" + (* In Markdown, HTML entities are supported directly, so we can just output them as text *) + [ Md.Inline.Text (s, Md.meta) ] + | Linebreak -> + (* In CommonMark, a hard line break can be represented by a backslash followed by a newline + or by two or more spaces at the end of a line. We'll use the hard break here. *) + (* We could use Thematic_break ? *) + let break = Md.Inline.Break.make `Hard in + [ Md.Inline.Break (break, Md.meta) ] | Styled (style, c) -> - failwith "inline not implemented styled" - (* let emph_level, app_style = styled style ~emph_level in - [ app_style @@ inline ~config ~emph_level ~resolve c ] *) - | Link { target = External href; content = c; _ } -> - failwith "inline not implemented ext link" - (* let a = (a :> Html_types.a_attrib Html.attrib list) in - let content = inline ~emph_level c in - [ Html.a ~a:(Html.a_href href :: a) content ] *) - | Link { target = Internal t; content; tooltip } -> - failwith "inline not implemented inline link" - (* internallink ~config ~emph_level ~resolve ~a t content tooltip *) - | Source c -> source (inline ~config ~emph_level ~resolve) c - | Math s -> (* [ inline_math s ] *) failwith "inline not implemented math" - | Raw_markup r -> - (* raw_markup r *) - failwith "inline not implemented markup!" + let inline_content = inline ~config ~emph_level ~resolve c in + styled ~emph_level style inline_content + | Link { target = External href; content; _ } -> + let inline_content = inline ~config ~emph_level ~resolve content in + let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in + let link_definition = + Md.Link_definition.make ~dest:(href, Md.meta) () + in + let link_reference = `Inline (link_definition, Md.meta) in + let inline_link = Md.Inline.Link.make link_inline link_reference in + [ Md.Inline.Link (inline_link, Md.meta) ] + | Link { target = Internal internal; content; tooltip = _ } -> + (* TODO: What's tooltip? *) + let href = + match internal with + | Resolved uri -> + (* TODO: Maybe internal links should be relative? *) + let url = Link.href ~config ~resolve uri in + (url, Md.meta) + | Unresolved -> + (* TODO: What's unresolved? A non-existing page/link? *) + ("", Md.meta) + in + let inline_content = inline ~config ~emph_level ~resolve content in + let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in + let link_definition = Md.Link_definition.make ~dest:href () in + let link_reference = `Inline (link_definition, Md.meta) in + let inline_link = Md.Inline.Link.make link_inline link_reference in + [ Md.Inline.Link (inline_link, Md.meta) ] + | Source c -> + (* Markdown doesn't allow any complex node inside inline text, right now rendering only Inline.Text nodes, in the future we can render everything as strings *) + let content = String.concat ~sep:"" (source inline_text_only c) in + [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] + | Math s -> + (* Since CommonMark doesn't support Math's, we just treat it as text. + | Ext_math_block of Code_block.t node + {{!Cmarkit.ext_math_display}display math} *) + [ Md.Inline.Text (s, Md.meta) ] + | Raw_markup _ -> + (* TODO: Is there any way to trick this? *) + failwith "Markdown doesn't support raw markup in inline text" in List.concat_map one l let heading ~config ~resolve (h : Heading.t) : Md.Block.t list = - let id = h.label in + (* TODO: Can I do something with the id? *) + let _id = h.label in let inlines = inline ~config ~resolve h.title in let content = Md.Inline.Inlines (inlines, Md.meta) in let heading = - Md.Block.Heading (Md.Block.Heading.make ~level:h.level content, Md.meta) + Md.Block.Heading + (Md.Block.Heading.make ~level:(h.level + 1) content, Md.meta) in [ heading ] -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 - -[@@@warning "-39"] - let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = let one (t : Block.one) : Md.Block.t list = - (* let mk_block ?(extra_class = []) mk content = - let a = Some (class_ (extra_class @ t.attr)) in - [ mk ?a content ] - in - let mk_media_block media_block target alt = - let block = - match target with - | Target.External url -> media_block url alt - | Internal (Resolved uri) -> - let url = Link.href ~config ~resolve uri in - media_block url alt - | Internal Unresolved -> - let content = [ Html.txt alt ] in - let a = Html.a_class [ "xref-unresolved" ] :: [] in - [ Html.span ~a content ] - in - mk_block Html.div block - in *) match t.desc with | Paragraph paragraph -> let inlines = inline ~config ~resolve paragraph in @@ -198,164 +158,228 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) in [ paragraph_block ] - | _ -> failwith "block not implemented" - (* match t.desc with - | Inline i -> - if t.attr = [] then as_flow @@ inline ~config ~resolve i - else mk_block Html.span (inline ~config ~resolve i) - | Paragraph i -> mk_block Html.p (inline ~config ~resolve i) | 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 - let term = - (inline ~config ~resolve i.Description.key - : phrasing Html.elt list - :> flow Html.elt list) - in - let def = block ~config ~resolve i.Description.definition in - Html.li ~a (term @ (Html.txt " " :: def)) + let list_type = + match typ with + | Ordered -> `Ordered (0, '.') + | Unordered -> `Unordered '-' in - mk_block Html.ul (List.map item l) - | Raw_markup r -> raw_markup r - | Verbatim s -> mk_block Html.pre [ Html.txt s ] - | Source (lang_tag, c) -> - let extra_class = [ "language-" ^ lang_tag ] in - mk_block ~extra_class Html.pre (source (inline ~config ~resolve) c) - | Math s -> mk_block Html.div [ block_math s ] - | Audio (target, alt) -> - let audio src alt = - [ - Html.audio ~src - ~a:[ Html.a_controls (); Html.a_aria "label" [ alt ] ] - []; - ] + let list_items = + List.map + (fun items -> + let block = block ~config ~resolve items in + let blocks = Md.Block.Blocks (block, Md.meta) in + (Md.Block.List_item.make blocks, Md.meta)) + l in - mk_media_block audio target alt - | Video (target, alt) -> - let video src alt = + [ + (* TODO: Do we need to make it tight based on something? *) + Md.Block.List + (Md.Block.List'.make ~tight:true list_type list_items, Md.meta); + ] + | Inline i -> + let inlines = Md.Inline.Inlines (inline ~config ~resolve i, Md.meta) in + [ Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) ] + | Table t -> + let rows_data : (string * [ `Data | `Header ]) list list = + match t.data with + | [] -> [] + | rows -> + List.map + (fun (row : (Block.t * [ `Data | `Header ]) list) -> + List.map + (fun (content, cell_type) -> + let cell_text = + String.concat ~sep:" " (block_text_only content) + in + (cell_text, cell_type)) + row) + rows + in + + (* If we have no data, return an empty paragraph *) + if rows_data = [] then [ - Html.video ~src - ~a:[ Html.a_controls (); Html.a_aria "label" [ alt ] ] - []; + Md.Block.Paragraph + ( Md.Block.Paragraph.make (Md.Inline.Inlines ([], Md.meta)), + Md.meta ); ] - in - mk_media_block video target alt - | Image (target, alt) -> - let image src alt = - let img = - Html.a - ~a:[ Html.a_href src; Html.a_class [ "img-link" ] ] - [ Html.img ~src ~alt () ] + else + (* Find maximum number of columns across all rows *) + let max_columns = + List.fold_left + (fun max_cols row -> + let row_cols = List.length row in + if row_cols > max_cols then row_cols else max_cols) + 0 rows_data in - [ img ] - in - mk_media_block image target alt *) - in - List.concat_map one l -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 *) - failwith "notimpemented" - -(* 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 -*) - -let spec_doc_div ~config ~resolve = function - | [] -> [] - | docs -> - (* let a = [ Html.a_class [ "spec-doc" ] ] in - [ div ~a (flow_to_item @@ block ~config ~resolve docs) ] *) - [] + (* Find out if we have a header row *) + let has_header_row = + match rows_data with + | first_row :: _ -> + List.exists + (fun (_, cell_type) -> cell_type = `Header) + first_row + | [] -> false + in -(* let rec documentedSrc ~config ~resolve (t : DocumentedSrc.t) : - item Html.elt list = - let open DocumentedSrc in - let take_code l = - Doctree.Take.until l ~classify:(function - | Code code -> Accum code - | Alternative (Expansion { summary; _ }) -> Accum summary - | _ -> Stop_and_keep) - in - let take_descr l = - Doctree.Take.until l ~classify:(function - | Documented { attrs; anchor; code; doc; markers } -> - Accum - [ { DocumentedSrc.attrs; anchor; code = `D code; doc; markers } ] - | Nested { attrs; anchor; code; doc; markers } -> - Accum - [ { DocumentedSrc.attrs; anchor; code = `N code; doc; markers } ] - | _ -> Stop_and_keep) - in - let rec to_html t = - match t with - | [] -> [] - | (Code _ | Alternative _) :: _ -> - let code, _, rest = take_code t in - source (inline ~config ~resolve) code @ to_html rest - | Subpage subp :: _ -> subpage ~config ~resolve subp - | (Documented _ | Nested _) :: _ -> - let l, _, rest = take_descr t in - let one { DocumentedSrc.attrs; anchor; code; doc; markers } = - let content = - match code with - | `D code -> (inline ~config ~resolve code :> item Html.elt list) - | `N n -> to_html n + (* Helper to create a list with n elements *) + let rec make_list n v = + if n <= 0 then [] else v :: make_list (n - 1) v + in + + (* Create table content with proper Markdown structure *) + let header_cells, content_rows = + match rows_data with + | first_row :: rest when has_header_row -> + (* Pad header cells to match max_columns *) + let padded_header = + let cells = List.map fst first_row in + let missing = max_columns - List.length cells in + if missing > 0 then cells @ make_list missing "" else cells + in + (padded_header, rest) + | _ -> + (* No header - create an empty header matching the max columns *) + (make_list max_columns "", rows_data) + in + + let pad_row row = + let cells = List.map fst row in + let missing = max_columns - List.length cells in + if missing > 0 then cells @ make_list missing "" else cells + in + + (* Create the header row as inline text *) + let header_inline = + let header_text = + "| " ^ String.concat ~sep:" | " header_cells ^ " |" + in + let header_md = Md.Inline.Text (header_text, Md.meta) in + Md.Inline.Inlines ([ header_md ], Md.meta) in - let doc = - match doc with - | [] -> [] - | doc -> - let opening, closing = markers in - let delim s = - [ Html.span ~a:(class_ [ "comment-delim" ]) [ Html.txt s ] ] + + (* Create the separator row (based on column alignment) *) + let separator_inline = + (* Ensure alignment list is the right length *) + let alignments = + if List.length t.align >= max_columns then + (* Take only the first max_columns elements *) + let rec take n lst = + if n <= 0 then [] + else match lst with [] -> [] | h :: t -> h :: take (n - 1) t in - [ - Html.div ~a:(class_ [ "def-doc" ]) - (delim opening @ block ~config ~resolve doc @ delim closing); - ] + take max_columns t.align + else + (* Pad with defaults *) + t.align + @ make_list (max_columns - List.length t.align) Table.Default + in + + let separator_cells = + List.map + (fun align -> + match align with + | Table.Left -> ":---" + | Table.Center -> ":---:" + | Table.Right -> "---:" + | Table.Default -> "---") + alignments + in + let sep_text = + "| " ^ String.concat ~sep:" | " separator_cells ^ " |" + in + let sep_md = Md.Inline.Text (sep_text, Md.meta) in + Md.Inline.Inlines ([ sep_md ], Md.meta) + in + + (* Create the content rows *) + let content_inlines = + List.map + (fun row -> + let cells = pad_row row in + let row_text = "| " ^ String.concat ~sep:" | " cells ^ " |" in + let row_md = Md.Inline.Text (row_text, Md.meta) in + Md.Inline.Inlines ([ row_md ], Md.meta)) + content_rows + in + + (* Build all rows in order: header, separator, content *) + let table_inlines = + [ header_inline; separator_inline ] @ content_inlines in - let extra_attr, extra_class, link = mk_anchor anchor in - let content = (content :> any Html.elt list) in - Html.li - ~a:(extra_attr @ class_ (attrs @ extra_class)) - (link @ content @ doc) + + (* Create paragraphs for each row *) + List.map + (fun inline -> + Md.Block.Paragraph (Md.Block.Paragraph.make inline, Md.meta)) + table_inlines + | Description _l -> + (* TODO: What's a description? *) + failwith "block not implemented: Description" + | Verbatim s -> + (* TODO: Not entirely sure if this is right, in HTML is `mk_block Html.pre [ Html.txt s ]` *) + let code_snippet = + Md.Block.Code_block + (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) + in + [ code_snippet ] + | Source (lang_tag, s) -> + let code_block = + s |> source inline_text_only |> List.map (fun s -> (s, Md.meta)) + in + let info_string = (lang_tag, Md.meta) in + let code_snippet = + Md.Block.Code_block + (Md.Block.Code_block.make ~info_string code_block, Md.meta) + in + [ code_snippet ] + | Math s -> + let math_as_inline_text = Md.Inline.Text (s, Md.meta) in + let inlines = Md.Inline.Inlines ([ math_as_inline_text ], Md.meta) in + let paragraph_block = + Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) + in + [ paragraph_block ] + | Raw_markup (target, content) -> ( + (* TODO: Is this correct? *) + match Astring.String.Ascii.lowercase target with + | "html" -> + let block_lines = Md.Block_line.list_of_string content in + [ Md.Block.Html_block (block_lines, Md.meta) ] + | _ -> []) + | Audio (_target, _alt) -> + (* TODO: Raise a decent error here? Only saw assert false :( *) + failwith "Audio isn't supported in markdown" + | Video (_target, _alt) -> + (* TODO: Raise a decent error here? Only saw assert false :( *) + failwith "Video isn't supported in markdown" + | Image (target, alt) -> + let dest = + match target with + | Target.External url -> (url, Md.meta) + | Target.Internal (Resolved uri) -> + let url = Link.href ~config ~resolve uri in + (url, Md.meta) + | Target.Internal Unresolved -> + (* TODO: What's unresolved? A non-existing page/link? *) + ("", Md.meta) in - Html.ol (List.map one l) :: to_html rest + let image = + Md.Inline.Link.make + (Md.Inline.Text (alt, Md.meta)) + (`Inline (Md.Link_definition.make ~dest (), Md.meta)) + in + [ + Md.Block.Paragraph + ( Md.Block.Paragraph.make + (Md.Inline.Inlines + ([ Md.Inline.Image (image, Md.meta) ], Md.meta)), + Md.meta ); + ] in - to_html t *) - -and subpage ~config:_ ~resolve:_ (_subp : Subpage.t) = - (* items ~config ~resolve subp.content.items *) - [] + List.concat_map one l and items ~config ~resolve l : Md.Block.t list = let rec walk_items acc (t : Item.t list) = @@ -376,11 +400,11 @@ and items ~config ~resolve l : Md.Block.t list = (continue_with [@tailcall]) rest (heading ~config ~resolve h) | Include { - attr; - anchor; - source_anchor; - doc; - content = { summary; status; content }; + attr = _attr; + anchor = _anchor; + source_anchor = _source_anchor; + doc = _doc; + content = { summary = _summary; status = _status; content = _content }; } :: rest -> (* let doc = spec_doc_div ~config ~resolve doc in @@ -417,7 +441,15 @@ and items ~config ~resolve l : Md.Block.t list = | `Default -> details ~open':true (* (Config.open_details config) *) in *) (continue_with [@tailcall]) rest content - | Declaration { Item.attr; anchor; source_anchor; content; doc } :: rest -> + | Declaration + { + Item.attr = _attr; + anchor = _anchor; + source_anchor = _source_anchor; + content = _content; + doc; + } + :: rest -> (* let extra_attr, extra_class, anchor_link = mk_anchor anchor in let link_to_source = mk_link_to_source ~config ~resolve source_anchor in let a = spec_class (attr @ extra_class) @ extra_attr in @@ -444,7 +476,7 @@ module Toc = struct let gen_toc ~config ~resolve ~path i = let toc = Toc.compute path ~on_sub i in let rec section { Toc.url; text; children } = - let text = inline ~config ~resolve text in + let _text = inline ~config ~resolve text in let title = (* (text) *) [] @@ -471,13 +503,13 @@ module Breadcrumbs = struct | { parent = None; _ } -> Some { Url.Path.parent = None; name = "index"; kind = `LeafPage } - let home_breadcrumb ~home_name config ~current_path ~home_path = + let home_breadcrumb ~home_name:_ config ~current_path ~home_path = let href = Some (Link.href ~config ~resolve:(Current current_path) (Odoc_document.Url.from_path home_path)) in - { href; name = [ Html.txt home_name ]; kind = `LeafPage } + { href; name = [ (* Html.txt home_name *) ]; kind = `LeafPage } let gen_breadcrumbs_no_sidebar ~config ~url = let url = @@ -489,7 +521,7 @@ module Breadcrumbs = struct match url with | { Url.Path.name = "index"; parent = None; kind = `LeafPage } -> let kind = `LeafPage in - let current = { href = None; name = [ Html.txt "" ]; kind } in + let current = { href = None; name = [ (* Html.txt "" *) ]; kind } in { parents = []; up_url = None; current } | url -> ( (* This is the pre 3.0 way of computing the breadcrumbs *) @@ -507,7 +539,7 @@ module Breadcrumbs = struct (Link.href ~config ~resolve:(Current url) (Odoc_document.Url.from_path path)) in - { href; name = [ Html.txt path.name ]; kind = path.kind } + { href; name = [ (* Html.txt path.name *) ]; kind = path.kind } in let parent_paths = get_parent_paths (List.rev (Odoc_document.Url.Path.to_list url)) @@ -545,7 +577,7 @@ module Breadcrumbs = struct let rec extract acc (tree : Odoc_document.Sidebar.t) = let parent = match find_parent tree with - | Some { node = { url; valid_link; content; _ }; children } -> + | Some { node = { url; valid_link; content = _; _ }; children } -> let href = if valid_link then Some (Link.href ~config ~resolve:(Current current_url) url) @@ -566,8 +598,8 @@ module Breadcrumbs = struct in { Types.current; parents = List.rev acc; up_url } | None -> - let kind = current_url.kind and name = current_url.name in - let current = { href = None; name = [ Html.txt name ]; kind } in + let kind = current_url.kind and _name = current_url.name in + let current = { href = None; name = [ (* Html.txt name *) ]; kind } in let up_url = List.find_map (fun (b : Types.breadcrumb) -> b.href) acc in @@ -625,8 +657,8 @@ module Page = struct ~breadcrumbs ~url ~uses_katex doc subpages and source_page ~config ~sidebar sp = - let { Source_page.url; contents } = sp in - let resolve = Link.Current sp.url in + let { Source_page.url; contents = _ } = sp in + let _resolve = Link.Current sp.url in let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~sidebar ~url in let sidebar = (* match sidebar with @@ -653,12 +685,13 @@ let render ~(config : Config.t) ~sidebar = function let filepath ~config url = Link.Path.as_filename ~config url -let doc ~config:_ ~xref_base_uri:_ _b = - (* let resolve = Link.Base xref_base_uri in - block ~config ~resolve b *) - Cmarkit.Doc.of_string ~layout:true ~strict:false "## Markdown" +(* TODO: Where is this beeing called? *) +let doc ~config ~xref_base_uri b = + let resolve = Link.Base xref_base_uri in + let block = block ~config ~resolve b in + let root_block = Md.Block.Blocks (block, Md.meta) in + Cmarkit.Doc.make root_block -let inline ~config:_ ~xref_base_uri:_ _b = - (* let resolve = Link.Base xref_base_uri in - inline ~config ~resolve b *) - [] +let inline ~config ~xref_base_uri b = + let resolve = Link.Base xref_base_uri in + inline ~config ~resolve b diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 307e4cf526..be89aea03b 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -2,10 +2,69 @@ $ ocamlc -c -bin-annot test2.mli $ printf "{0 The title}\n something else" > page.mld $ odoc compile --package test test.cmti + File "test.mli", line 1, characters 4-12: + Warning: '{0': heading level should be lower than top heading level '0'. $ odoc compile --package test -I . test2.cmti $ odoc compile --package test -I . page.mld $ odoc link test.odoc + File "test.mli", line 304, characters 32-75: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).tags Couldn't find page "odoc_for_authors" + File "test.mli", line 293, characters 12-47: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).tags Couldn't find page "odoc_for_authors" + File "test.mli", line 230, characters 12-45: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).tables Couldn't find "odoc_for_authors" + File "test.mli", line 224, characters 10-43: + Warning: Failed to resolve reference ./odoc_logo_placeholder.jpg Path 'odoc_logo_placeholder.jpg' not found + File "test.mli", line 215, characters 12-45: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).media Couldn't find "odoc_for_authors" + File "test.mli", line 196, characters 12-42: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).math Couldn't find "odoc_for_authors" + File "test.mli", line 187, characters 12-57: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).verbatim_blocks Couldn't find "odoc_for_authors" + File "test.mli", line 152, characters 12-56: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).code_blocks Couldn't find "odoc_for_authors" + File "test.mli", line 115, characters 12-44: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).lists Couldn't find "odoc_for_authors" + File "test.mli", line 110, characters 14-68: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).links_and_references Couldn't find "odoc_for_authors" + File "test.mli", line 108, characters 14-67: + Warning: Failed to resolve reference /cmdliner/tutorial Path '/cmdliner/tutorial' not found + File "test.mli", line 106, characters 14-64: + Warning: Failed to resolve reference /fmt/Fmt.pf Path '/fmt/Fmt' not found + File "test.mli", line 104, characters 14-57: + Warning: Failed to resolve reference unresolvedroot(Odoc_odoc).Compile.compile Couldn't find "Odoc_odoc" + File "test.mli", line 102, characters 14-42: + Warning: Failed to resolve reference unresolvedroot(Odoc_odoc).Compile.compile Couldn't find "Odoc_odoc" + File "test.mli", line 87, characters 12-64: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).links_and_references Couldn't find "odoc_for_authors" + File "test.mli", line 72, characters 12-58: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).links_and_references Couldn't find "odoc_for_authors" + File "test.mli", line 63, characters 12-66: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).basics Couldn't find "odoc_for_authors" + File "test.mli", line 54, characters 12-65: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).basics Couldn't find "odoc_for_authors" + File "test.mli", line 27, characters 12-50: + Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).sections Couldn't find "odoc_for_authors" $ odoc link test2.odoc $ odoc link page-page.odoc $ odoc markdown-generate test.odocl -o markdown + # Test + ## Test + Quick reference for the odoc language\! + \| \| odoc syntax \| Render as \| + \| --- \| --- \| --- \| + \| Paragraphs \| A first paragraph A second paragraph \| A first paragraph A second paragraph \| + \| Headings \| {1 Title} {2 Subtitle} {3 Subsubtitle} {3:my\_id Referenceable title} See {!my\_id}. Standalone pages must start with a 0 heading: {0 Page big title} \| See \| + \| Bold, italic and emphasis \| {b bold} text, {i italic} text, {e emphasized} text \| bold text, italic text, emphasized text \| + \| Subscripts and superscript \| H{\_ 2}O and 1{^ st} \| H 2 O and 1 st \| + \| Link \| Here is a link: {:https://www.example.com}. You can also click {{:https://www.example.com}here}. \| Here is a link: https://www.example.com . You can also click here . \| + \| References \| See {!Odoc\_odoc.Compile.compile}. See {{!Odoc\_odoc.Compile.compile}this function}. See {{!/fmt/Fmt.pf}this function from another library}. See {{!/cmdliner/tutorial}this page from another package}. See {{!odoc\_for\_authors.links\_and\_references}this section} for the syntax of references. \| See Odoc\_odoc.Compile.compile . See this function . See this function from another library . See this page from another package . See this section for the syntax of references. \| + \| Lists \| - First item - Second item + First ordered item + Second numbered item {ul {- First item} {- Second item} {li can also be used}} {ol {- First numbered item} {- Second numbered item} {li can also be used}} \| First item Second item First ordered item Second numbered item First item Second item can also be used First numbered item Second numbered item can also be used \| + \| Code Blocks \| Inline \[code\]. {\[ let \_ = "Block code" \]} {foo@text\[ Code block with {\[inner code block syntax\]} \]foo} {@python\[ \[i+1 for i in xrange(2)\] \]} \| Inline code . let \_ = "Block code" Code block with {\[inner code block syntax\]} \[i+1 for i in xrange(2)\] \| + \| Verbatim \| {v verbatim text v} \| verbatim text \| + \| Math \| For inline math: {m \\sqrt 2}. For display math: {math \\sqrt 2} \| For inline math: . For display math: \| + \| Images \| {image!path/to/file.png} {image:https://picsum.photos/200/100} \| \| + \| Table \| Light syntax: {t \| Header 1 \| Header 2 \| \|----------\|----------\| \| Cell 1 \| Cell 2 \| \| Cell 3 \| Cell 4 \|} Explicit syntax: {table {tr {th Header 1} {th Header 2}} {tr {td Cell 1} {td Cell 2}} {tr {td Cell 3} {td Cell 4}}} \| Light syntax: Explicit syntax: \| + \| HTML \| {%html: \ Odoc language lack support for quotation! \ %} \| \| + \| Tags \| @since 4.08 Tags are explained in {{!page-odoc\_for\_authors.tags}this section}. \| Since 4.08. Tags are explained in this section . \| $ cat markdown/test/Test.html diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli index 4bc52ea372..744d39185c 100644 --- a/test/integration/markdown.t/test.mli +++ b/test/integration/markdown.t/test.mli @@ -1,9 +1,307 @@ -(** Test *) - -(** {1 Section 1} *) +(** {0 Test} *) type t -(** {1 Section 2} *) +(** {1 Test} *) + +(** Quick reference for the odoc language! + + {table + {tr {th } {th [odoc] syntax } {th Render as } } + {tr + {th Paragraphs } + {td + {@text[ + A first paragraph + + A second paragraph + ]} + } + {td + A first paragraph + + A second paragraph + } + } + {tr + {th {{!odoc_for_authors.sections}Headings} } + {td + {@text[ + {1 Title} + {2 Subtitle} + {3 Subsubtitle} + + {3:my_id Referenceable title} + + See {!my_id}. + ]} + + Standalone pages must start with a [0] heading: + + {@text[ + {0 Page big title} + ]} + } + {td + {%html:

Title

%} {%html:

Subtitle

%} + {%html:

Subsubtitle

%} + {%html:

Referenceable title

%} + + See {%html:
Referenceable title%} + } + } + {tr + {th {{!odoc_for_authors.basics}Bold, italic and emphasis} } + {td + {@text[ + {b bold} text, {i italic} text, {e emphasized} text + ]} + } + {td {b bold} text, {i italic} text, {e emphasized} text } + } + {tr + {th {{!odoc_for_authors.basics}Subscripts and superscript} } + {td + {@text[ + H{_ 2}O and 1{^ st} + ]} + } + {td H{_ 2}O and 1{^ st} } + } + {tr + {th {{!odoc_for_authors.links_and_references}Link} } + {td + {@text[ + Here is a link: {:https://www.example.com}. + + You can also click {{:https://www.example.com}here}. + ]} + } + {td + Here is a link: {:https://www.example.com}. + + You can also click {{:https://www.example.com}here}. + } + } + {tr + {th {{!odoc_for_authors.links_and_references}References} } + {td + {@text[ + See {!Odoc_odoc.Compile.compile}. + + See {{!Odoc_odoc.Compile.compile}this function}. + + See {{!/fmt/Fmt.pf}this function from another library}. + + See {{!/cmdliner/tutorial}this page from another package}. + + See {{!odoc_for_authors.links_and_references}this section} for the syntax of references. + ]} + } + {td + See {!Odoc_odoc.Compile.compile}. + + See {{!Odoc_odoc.Compile.compile}this function}. + + See {{!/fmt/Fmt.pf}this function from another library}. + + See {{!/cmdliner/tutorial}this page from another package}. + + See {{!odoc_for_authors.links_and_references}this section} for the + syntax of references. + } + } + {tr + {th {{!odoc_for_authors.lists}Lists} } + {td + {@text[ + - First item + - Second item + + + First ordered item + + Second numbered item + + {ul + {- First item} + {- Second item} + {li can also be used}} + + {ol + {- First numbered item} + {- Second numbered item} + {li can also be used}} + ]} + } + {td + - First item + - Second item + + + First ordered item + + Second numbered item + + - First item + - Second item + - can also be used + + + First numbered item + + Second numbered item + + can also be used + } + } + {tr + {th {{!odoc_for_authors.code_blocks}Code Blocks} } + {td + {example@text[ + Inline [code]. + + {[ + let _ = "Block code" + ]} + + {foo@text[ + Code block with {[inner code block syntax]} + ]foo} + + {@python[ + [i+1 for i in xrange(2)] + ]} + ]example} + } + {td + Inline [code]. + + {[ + let _ = "Block code" + ]} + + {foo@text[ + Code block with {[inner code block syntax]} + ]foo} + + {@python[ + [i+1 for i in xrange(2)] + ]} + } + } + {tr + {th {{!odoc_for_authors.verbatim_blocks}Verbatim} } + {td + {example@text[ + {v verbatim text v} + ]example} + } + {td {v verbatim text v} } + } + {tr + {th {{!odoc_for_authors.math}Math} } + {td + {@text[ + For inline math: {m \sqrt 2}. + + For display math: + + {math \sqrt 2} + ]} + } + {td + For inline math: {m \sqrt 2}. + + For display math: + + {math \sqrt 2} + } + } + {tr + {th {{!odoc_for_authors.media}Images} } + {td + {@text[ + {image!path/to/file.png} + + {image:https://picsum.photos/200/100} + ]} + } + {td + {image!odoc_logo_placeholder.jpg} + + {image:https://picsum.photos/200/100} + } + } + {tr + {th {{!odoc_for_authors.tables}Table} } + {td + {@text[ + Light syntax: + + {t | Header 1 | Header 2 | + |----------|----------| + | Cell 1 | Cell 2 | + | Cell 3 | Cell 4 |} + + Explicit syntax: + + {table + {tr + {th Header 1} + {th Header 2}} + {tr + {td Cell 1} + {td Cell 2}} + {tr + {td Cell 3} + {td Cell 4}}} + ]} + } + {td + Light syntax: + + {t + | Header 1 | Header 2 | + |----------|----------| + | Cell 1 | Cell 2 | + | Cell 3 | Cell 4 | + } + + Explicit syntax: + + {table + {tr {th Header 1 } {th Header 2 } } + {tr {td Cell 1 } {td Cell 2 } } + {tr {td Cell 3 } {td Cell 4 } } + } + } + } + {tr + {th HTML } + {td + {example@text[ + {%html: +
+ Odoc language lack support for quotation! +
+ %} + ]example} + } + {td + {%html: +
+ Odoc language lack support for quotation! +
+ %} + } + } + {tr + {th {{!page-odoc_for_authors.tags}Tags} } + {td + {example@text[ + @since 4.08 + + Tags are explained in {{!page-odoc_for_authors.tags}this section}. + ]example} + } + {td + Since 4.08. -type u + Tags are explained in {{!page-odoc_for_authors.tags}this section}. + } + } + } *) From 30868084e153c6aafd5f9e7a7af3d33f3975278b Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Tue, 18 Mar 2025 14:20:30 +0100 Subject: [PATCH 07/53] Support Description --- src/markdown2/generator.ml | 18 +++++++++++++++--- 1 file changed, 15 insertions(+), 3 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index c970642de6..65a6aa50a6 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -315,9 +315,21 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = (fun inline -> Md.Block.Paragraph (Md.Block.Paragraph.make inline, Md.meta)) table_inlines - | Description _l -> - (* TODO: What's a description? *) - failwith "block not implemented: Description" + | Description l -> + let item ({ key; definition; attr = _ } : Description.one) = + let term = inline ~config ~resolve key in + (* We extract definition as inline, since it came as "Block". There seems to be no way (in Cmarkit) to make it inline *) + let definition_inline = + Md.Inline.Text + (String.concat ~sep:" " (block_text_only definition), Md.meta) + in + let space = Md.Inline.Text (" ", Md.meta) in + let term_inline = + Md.Inline.Inlines (term @ [ space; definition_inline ], Md.meta) + in + [ Md.Block.Paragraph (Md.Block.Paragraph.make term_inline, Md.meta) ] + in + List.concat_map item l | Verbatim s -> (* TODO: Not entirely sure if this is right, in HTML is `mk_block Html.pre [ Html.txt s ]` *) let code_snippet = From fa75269e78cf3b2e0604465cdf4188c543ed0674 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Tue, 18 Mar 2025 14:20:41 +0100 Subject: [PATCH 08/53] Improve carm tests for markdown --- .../markdown.t/odoc_logo_placeholder.jpg | Bin 0 -> 5604 bytes test/integration/markdown.t/page.mld | 120 +++++++ test/integration/markdown.t/run.t | 182 ++++++---- test/integration/markdown.t/test.mli | 310 +----------------- 4 files changed, 246 insertions(+), 366 deletions(-) create mode 100644 test/integration/markdown.t/odoc_logo_placeholder.jpg create mode 100644 test/integration/markdown.t/page.mld diff --git a/test/integration/markdown.t/odoc_logo_placeholder.jpg b/test/integration/markdown.t/odoc_logo_placeholder.jpg new file mode 100644 index 0000000000000000000000000000000000000000..129c4cd6f7d923811c1558a6dc12857e7263521a GIT binary patch literal 5604 zcmb7|XEYmt*Ty46>=~QdBZ*z3HnFK4d)3|}Mk(5wHClU=6eYE15rnq1W=qi$l-PSz z6}8*?_kZ3G?>Xd_bOt*5IshUfBEY?W1-KyqGyz}`h!jKu zCIyj_fx%=H^pq6j>x!U~Y0 zK408qnvw-Vq)O40NQPJRKwH@?jV^0n;}yg-vE{CrK@KA(Uy&}&rrJ>EOHt+B$%;hR zIO8;L9g#uF+qNWM@@IHuvy6>Uhf#HNuA@O+<2hD&4LY#@aJ+! ze(9esDGhS%KT!Fi6^yauDo>W&EdxCHCE}+dLKdg(rakG37DShXA8X4QfDJYsPqi~X zgvJHFbtp;|-)JIhlu#Q`Ag*EM$dX2N)x9y_hfkjr^DQ(p14q8h+qX2Pu5O6l0BF?x zN#2b*w&l+IqJhj86RBUPM*%>}`U|(#QI;w_TIrF5&raXXWzL#BI0vOqd<|Jh zsDM=?9Ulq)rG#wUniL9W_mWTa`MMZMe4c1ENjQlWlQFNDKsTdq_BV}7^m0YtTH{k= zHsyYA{w;%}LDsshi8W+ZUcn(%mEl8$#@PJKWX&t&6(KY!GX3;vSmN8b^Vm5(RjqKQ z5OfFo%hTeEAY@$)3`%=x|D3)hXpkwJRW<{*hGD>@L4`_0O-0Jd(NHu}Anl$xu#LPb zaS|pNiD#i~=oGWlu2jZ;|5XuYf-%v!>~RWjcG#2E^7~#0=RHq8$}6qa-^t#49P|(o zZaMfd!q6%4+2(YI1>=5a)ps-e_by7aGgb=jVEQhBxMx;=72(Jsw6KjlUUw(D@y=R+ zfLLvQr}(dgw%RkwIqCiYY@@+6d+V6Lse&Dgh}h@94hiU)g{K*<9qB5onkO#y^t=*A z_`_O%K?Cl%yk|_?#44nOOZ@O%Z!s4C7TM6pI{j@80*$UabSGngN5?amGIEZRvoZbU zV8;gWbcy?Eqs7Wno04?bMm1p|e%F_hlEL?RrqldYOY`T=o?YZKSqWMo7sEvwu)WIR5d$xZpSndQse6>|q-}4T) z_t3%>jSC=%S$TcC%W4+4Ipi5EAGaQw{_8f4FrRm88jNGV(5t#ubFmL z(LDIxzYqH|teXho&wUGvB%Lk9t8qV+Q+}wxKcNTE$JByVD_ieI3ul3|l<`fC5_N8S zcamV_o_;=~&$c~iw@j)J95Ka~!m_G^OLQX#O5E} z%g3VOw|=ZozI(*s+#uhdi&ukxSiA77Ib@d5_|3f^f3_B9%Wl({l$cc=rvo)dj1)k> zA{c?#1ut3u4n6b@V8H`qbE1+wuwwOV3!}>G$i$$`+DJc8t+_|y<<8Y{{&(7`&V@ug zH@;oh*w>eXg?r|d?ppO!E@-~lz7oe7cE>@qK1r*_Ehg;1PU31LD7jQ*Z*;Q`9}eoU zFf+n;U=jkup{s_zp&((Njf^?A;h0nAx}IHUj)5&v7LIpKew-+4woekFee-i7`p!_+ zP&Q5_>g(BV$mJEcF+t3@fV2DE_=~6jeM-Y-RSYKSGK)qPSf>fGK?dd@iqo|Ainh5< zwlYh~bo}XY?>bS|%x(w(ET0Ny>g`^7_qVJVF^Wr@MwJC`KhJLIi+l&us8TlnIr638 zyPV*koGBNmUKCpfOI)nJ6-8!UXOpI4l~~twugjF2l0)U6U8ywziIrd}yKs-`H|I%; zIqS762;3W@JU)(bN#d07!Qgm^Jb~x$Wi4i4cTbRRFuK%M#Iw)Wr~I}7C|P+L*Qo8K zbsHL?SL*^@6Ni3b02j$pJ#S>2R%PF}uaIl=NgGJ{SpmsD%_?}<9vh9y0e9EZf|cb` zo3?rmc4z-iq`g)UlSoFRa&x~0k`fM`5&KUy>6N*A?HZ2kGy3J8zi@eyn^-}T8>>o+ zwa3N>wr0FnZ+)fq0d;_8lYfI9ws#dONma@j2(A>Hgy9MQBL&l&r$834)hZ!`N48|FynMSt<*3Ki58YE`F0jPtH=92rUJ07zI_xXapM zmgXp;D5kX5VrffJU5@}D`T|g-IJwwF8hgdH&w??h+$QFC1!m;r2EupVo?XY(7Y}I1 zkCZ;>Pb^nk>YwRmAw%m7!uJ$2ZMD*acW_5V7QbI@U`mrW4K2itOMZ?E_$eoU!?R<| z-3IT*fURbN&6%d53T*rj-=8*Zp|8|@yqPP6&14RiRgMCllBkFhZA`C@c1ZJYUHN!k!)pWmQcfQDpnd23;DyNi{3Ath6oDXch zLrK=L%%+|3sL;x-Sc&W2c4~WIZs}iViujI9)9khntv3MGLC1c-8$e#_uXfe?fc1$Q zYxEQHF*k=l@*(o+w@H1+9qcv4AB9~DpR!%d>T=9t+!E$F<(Sr;`Z+!a&Qll2)Rtnc z{SuFi3!rIwwq@=}CENFHb>>^k%|`Dv9iA{qm0C+_ffRn1>+*=Kcs1%ZXF9IUaX&U1 zOc!5UrkKx!dXPm>fb`e6$k_lTZO^7j9fHjC3*Hny{3X}PXW*-`Ig&W_RA3+{_X0S< zDDem1KvJIw4|F!+(hL(|q0sXcsD7ME-(nS01Sfl={xt&Hpx_>zt+>>_=|ckK(zWO- z3+-$+NNAyP?7J6Gu#k0KH%^MIK?6GPv%Dp*e%6hE~pelu+yVLnr&8Jlq_wywE-GNY z*#UMyTwbk*eQ7nY%D=LNtG2NCw%imnADWEj)!4EsNl_tZzt2Pd07W;g=lE)wBCQ-i&8^y!?lH{lWMWH80P9LSN> z9jSq6C$Ao6(yh&9)!a`#8+y)`SCiLWmZO4+s>!Q=ENgkyKlaguR=P=OLC@TzPF_a1j)bdQr<6}uRP(h4 zR6=qi-pG6%MOBZ%ebfL%YKpaH$y4|d!JPBuF>iC%d}KDO8{crokEbsx%wx2U^cDM* zz1XL$$cC7TyW>lvUnJehil%z`N7ob;L}a(F?I~cjuIcdNookW-?X2cS`W_rUE zd2Cx^4Lo@DeHISdn=HILTiJ*1QRx!g1B*UFIEs3WF|+=IMcvlqnvT=#&N2`kZD$a2lF13xv|crUV} zin4nTst29L&S;%I9ET!45Eji08HJt=3-wi3mm2tJwQ%Q9VWxV<;*oDp#eY(Ym73 z)DkJ?o{d_IeM2T#oV)Qa3Y|E8N>>x#C;KJ98BE^T{Gb?fiD@5%-w+V|Nu8th*mzU} z%#jcqMc;mx(V@|j{?dwtE54G?U0Oi0B77t&?vSm?>0GDp?CD$tBp^q9n1lG8rP`WK z)69P86c#cZo?hJj@yWWlEIB69yn5k*JxL;u8;nqeN-*{7dHambJn;6`ghQgBVaGg& z+&3-yR;%672?3fCQq|o-+wSs1l;4{5daj2og;sp=$d}ur!hnq3RYze^0bf- z9Wn0$HGSIqI_wW>@7$kd7cpco)qy0Zjx3Ncs8n)>v+`J$U?k44_OEs?bC|;_7biuh zxUCru7_RF0t4D?BR3J3brR;X+t}m;bgh107cQY)4f|Eeea6NNl-SVcbxP+Ll(cGYR z8~5dawk-A%re+Tk>d79LGkZIlU9(->0t40Lz$aF_)ofGE+iQ{0Mk&@TDN)9oF<-~T zZ~GcoPQqYhI(v`gO)DPDNs|4p2$!Au**vIcT^KJ=$-IOBE(LMOVSQR1`Bc5&Gh(#*@dXBvRkm-3$)9%CvM8*PpbG%Yvnv%er>Os zj&uR+U$GLc$%V2tEqLy`y5#AvjN>kz!F~_ER~PC(Ts*AG|D0xY*J?p?ta7M;If*Js zV1xaqQ&7P*Bt*N_m;n6%IviRXNry!Z$-eYz7J4}dO6LvS=3QXt^yAAH1V5`1~ zmoYKALvISwO-nr1$4h8FXNrqbh9$2b>p{2aG?X6k04^;HR0ij1eZWVH=F#jN6~jO^ zmHfrDnW+QiYKGAol#xWiib0%+7164yE(vGU%))_XuJzEtvfkYN4Lw8D4>_w@UV&BR zGdzN6CsOVbStqE#g4@UcuzA!hs;{L1FSb!m5~xom8ZTBqYxcRb@1SoLjeYT`JQI%W zo?_v@0jQsd3APi=E#eu<9yXqT`mo<)6j`+=KsdN-zoPFr9;u0%g1(nr$B|R0`U*en z*f;xl_S)0h-|b}qBa zyBfnC-HWI6>T;0;_niZqg=-hF*0sy8ctwG~0^En?jg#0vr5iz=9gvz1F$-#H$EVcK znMf`C*5Kx(zbQyI9W%DwvfZ6UTiQXDAEnPI&Rzsl6P!J04^ftkCQdS3NAKM+9I4j} z!vLR+Go>uD(>)b9r0bji;22B#f;{(2X{UUQvR$F<51>_$((pu4P4Y8FjMN%dOq*HM zu(I*n_kyBGl*~{6;9B7+RKg8_$%PgYX0-Qt6m_b3<#|V)qN9r3gy;v6|Gi99%~m7! z!moa{ZsnbZ?-Wbp$kZ)_qs!)lf~hYrr4qK$m0s#dg>jus!PFg%KIbRMjv3`4bu}sb z@)mrb%wZ7DDb&EgCnKpzk^4Km)GIZL*w}*rfp+JtK)foas(wOB(6VC!82;zO zdroX85x8zkAA$O*FZ`=s9&rIuGF)C+7Vr(La@W1nZ|1s5!P=LD#E_FPC`L4qT_OCC zUHLvDG2Ek{vS=sN4jlD*^+scL#1(}QOpAAwF{%dYfA+le0)*bda}OK7oVmikAOo>3DPvVdl1E+G&p$^$@oS zDH}N|q_C8%;|)F3cK*QnQ@E|lCk5ecGif#ED^0kq-Y%8gSA|7~po_M9fvUDzv-#;S zHc9?gtW~KpQWmt}xU9qOX|?ym0tu{~CtUnVK_Y*}=?rxJYi)Kd!B1|nf1W*W=;m~t zVAI?Wc`|o6s_~=kih9ETj}HaJ&*NQ++!_5XQO|xOnYh@*^jId=swa&1pUryK`Dho1 z*wfl+SyY5Niu57Pw8^WyAsvhjiJJ+$2n50P5=bOPOZWSJmGC+^6UDeQbkdk|&d@5eLOq|mXP zrMusn(4QalL@lmnPXENR#rMxXz7a8Lk+_%m@{{)s0KF*DS3Rj87aHK!>g-?fd&sY# zmqy|shhZTCjCSTeOezjFNr`jI7mhB-FV?$1?Ps9VL>EnGO0>TJlOEz6 zxOB93eJ}qpQoH(0s5?C}=uz;h&$BNl7At?>&)TshrL9rm7AC=A!$HDZ%@<9wcC{I( z2;qg=@NRb0=JVGi@=8Rlc5;7m;Go2k8=t80TeyFy!#PkTd+(8@ z8g}=oc2*K1r8M{kU^_L`8>gbm+EiPc<~Jtkt?z}lZ3s0;6m2ueXDe6YOGBEXp%#@0#!BOSGTZC~ zn;Fl1a#8Pw-A6FGmO;q%q>48Jr2OycL^cT7;qpcxEh?811&!nGnkHpHry8QaB;GHx U;M(EZK|n3Is6Emcop0v;0~EwAI{*Lx literal 0 HcmV?d00001 diff --git a/test/integration/markdown.t/page.mld b/test/integration/markdown.t/page.mld new file mode 100644 index 0000000000..d5ce3225c0 --- /dev/null +++ b/test/integration/markdown.t/page.mld @@ -0,0 +1,120 @@ +{0 The title} + +Quick reference for the odoc language rendering markdown + +{1 Title} +{2 Subtitle} +{3:my_id Referenceable title} + +See {!my_id}. + +{3:styled Styled} + +{b bold} text, {i italic} text, {e emphasized} text + +H{_ 2}O and 1{^ st} + +{3 Link} + +Here is a link: {:https://www.example.com}. + +You can also click {{:https://www.example.com}here}. + +{3 References} + +See [Odoc_odoc.Compile.compile]. + +See [Odoc_odoc.Compile.compile]. + +See {{!/test.v}this function from another library}. + +See {{!./test.mli}this page from another package}. + +See {{!styled}this section} for the syntax of references. + +{3 Lists} + +- First item +- Second item + ++ First ordered item ++ Second numbered item + +{ul + {- First item} + {- Second item} + {li can also be used}} + +{ol + {- First numbered item} + {- Second numbered item} + {li can also be used}}} + + +{3 Code blocks} + +Inline [code]. + +{[ +let _ = "Block code" +]} + +{foo@text[ +Code block with {[inner code block syntax]} +]foo} + +{@python[ +[i+1 for i in xrange(2)] +]}} + +{3 Verbatim} + +{v verbatim text v} + +{3 Math} + +For inline math: {m \sqrt 2}. + +For display math: + +{math \sqrt 2} + +{3 Images} + +{image!odoc_logo_placeholder.jpg} +{image:https://picsum.photos/200/100} + +{3 Table} + +{4 Explicit syntax} + +{table + {tr + {th Header 1} + {th Header 2}} + {tr + {td Cell 1} + {td Cell 2}} + {tr + {td Cell 3} + {td Cell 4}}}]}} + +{4 Light syntax} + +{t | Header 1 | Header 2 | + |----------|----------| + | Cell 1 | Cell 2 | + | Cell 3 | Cell 4 |} + +{3 HTML} + +{%html: +
+ Odoc language lack support for quotation! +
+%}} + +{3 Tags} + +@since 4.08 +Tags are explained in this section. diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index be89aea03b..75ce77900a 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -1,70 +1,128 @@ $ ocamlc -c -bin-annot test.mli $ ocamlc -c -bin-annot test2.mli - $ printf "{0 The title}\n something else" > page.mld + $ odoc compile --package test -I . page.mld + File "page.mld", line 33, characters 4-12: + Warning: '{{links}': bad markup. + Suggestion: did you mean '{!{links}' or '[{links]'? + File "page.mld", line 33, characters 24-25: + Warning: Unpaired '}' (end of markup). + Suggestion: try '\}'. + File "page.mld", line 51, characters 24-25: + Warning: Unpaired '}' (end of markup). + Suggestion: try '\}'. + File "page.mld", line 68, characters 2-3: + Warning: Unpaired '}' (end of markup). + Suggestion: try '\}'. + File "page.mld", line 100, characters 19-20: + Warning: Unpaired '}' (end of markup). + Suggestion: try '\}'. + File "page.mld", line 115, characters 2-3: + Warning: Unpaired '}' (end of markup). + Suggestion: try '\}'. + File "page.mld", line 119, characters 0-11: + Warning: Tags are not allowed in pages. $ odoc compile --package test test.cmti - File "test.mli", line 1, characters 4-12: - Warning: '{0': heading level should be lower than top heading level '0'. + $ ls + odoc_logo_placeholder.jpg + page-page.odoc + page.mld + test.cmi + test.cmti + test.mli + test.odoc + test2.cmi + test2.cmti + test2.mli $ odoc compile --package test -I . test2.cmti - $ odoc compile --package test -I . page.mld $ odoc link test.odoc - File "test.mli", line 304, characters 32-75: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).tags Couldn't find page "odoc_for_authors" - File "test.mli", line 293, characters 12-47: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).tags Couldn't find page "odoc_for_authors" - File "test.mli", line 230, characters 12-45: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).tables Couldn't find "odoc_for_authors" - File "test.mli", line 224, characters 10-43: - Warning: Failed to resolve reference ./odoc_logo_placeholder.jpg Path 'odoc_logo_placeholder.jpg' not found - File "test.mli", line 215, characters 12-45: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).media Couldn't find "odoc_for_authors" - File "test.mli", line 196, characters 12-42: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).math Couldn't find "odoc_for_authors" - File "test.mli", line 187, characters 12-57: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).verbatim_blocks Couldn't find "odoc_for_authors" - File "test.mli", line 152, characters 12-56: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).code_blocks Couldn't find "odoc_for_authors" - File "test.mli", line 115, characters 12-44: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).lists Couldn't find "odoc_for_authors" - File "test.mli", line 110, characters 14-68: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).links_and_references Couldn't find "odoc_for_authors" - File "test.mli", line 108, characters 14-67: - Warning: Failed to resolve reference /cmdliner/tutorial Path '/cmdliner/tutorial' not found - File "test.mli", line 106, characters 14-64: - Warning: Failed to resolve reference /fmt/Fmt.pf Path '/fmt/Fmt' not found - File "test.mli", line 104, characters 14-57: - Warning: Failed to resolve reference unresolvedroot(Odoc_odoc).Compile.compile Couldn't find "Odoc_odoc" - File "test.mli", line 102, characters 14-42: - Warning: Failed to resolve reference unresolvedroot(Odoc_odoc).Compile.compile Couldn't find "Odoc_odoc" - File "test.mli", line 87, characters 12-64: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).links_and_references Couldn't find "odoc_for_authors" - File "test.mli", line 72, characters 12-58: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).links_and_references Couldn't find "odoc_for_authors" - File "test.mli", line 63, characters 12-66: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).basics Couldn't find "odoc_for_authors" - File "test.mli", line 54, characters 12-65: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).basics Couldn't find "odoc_for_authors" - File "test.mli", line 27, characters 12-50: - Warning: Failed to resolve reference unresolvedroot(odoc_for_authors).sections Couldn't find "odoc_for_authors" $ odoc link test2.odoc $ odoc link page-page.odoc + File "page.mld", line 84, characters 0-33: + Warning: Failed to resolve reference ./odoc_logo_placeholder.jpg Path 'odoc_logo_placeholder.jpg' not found + File "page.mld", line 31, characters 4-49: + Warning: Failed to resolve reference ./test.mli Path 'test' not found + File "page.mld", line 29, characters 4-50: + Warning: Failed to resolve reference /test.v Path '/test' not found $ odoc markdown-generate test.odocl -o markdown - # Test - ## Test - Quick reference for the odoc language\! - \| \| odoc syntax \| Render as \| - \| --- \| --- \| --- \| - \| Paragraphs \| A first paragraph A second paragraph \| A first paragraph A second paragraph \| - \| Headings \| {1 Title} {2 Subtitle} {3 Subsubtitle} {3:my\_id Referenceable title} See {!my\_id}. Standalone pages must start with a 0 heading: {0 Page big title} \| See \| - \| Bold, italic and emphasis \| {b bold} text, {i italic} text, {e emphasized} text \| bold text, italic text, emphasized text \| - \| Subscripts and superscript \| H{\_ 2}O and 1{^ st} \| H 2 O and 1 st \| - \| Link \| Here is a link: {:https://www.example.com}. You can also click {{:https://www.example.com}here}. \| Here is a link: https://www.example.com . You can also click here . \| - \| References \| See {!Odoc\_odoc.Compile.compile}. See {{!Odoc\_odoc.Compile.compile}this function}. See {{!/fmt/Fmt.pf}this function from another library}. See {{!/cmdliner/tutorial}this page from another package}. See {{!odoc\_for\_authors.links\_and\_references}this section} for the syntax of references. \| See Odoc\_odoc.Compile.compile . See this function . See this function from another library . See this page from another package . See this section for the syntax of references. \| - \| Lists \| - First item - Second item + First ordered item + Second numbered item {ul {- First item} {- Second item} {li can also be used}} {ol {- First numbered item} {- Second numbered item} {li can also be used}} \| First item Second item First ordered item Second numbered item First item Second item can also be used First numbered item Second numbered item can also be used \| - \| Code Blocks \| Inline \[code\]. {\[ let \_ = "Block code" \]} {foo@text\[ Code block with {\[inner code block syntax\]} \]foo} {@python\[ \[i+1 for i in xrange(2)\] \]} \| Inline code . let \_ = "Block code" Code block with {\[inner code block syntax\]} \[i+1 for i in xrange(2)\] \| - \| Verbatim \| {v verbatim text v} \| verbatim text \| - \| Math \| For inline math: {m \\sqrt 2}. For display math: {math \\sqrt 2} \| For inline math: . For display math: \| - \| Images \| {image!path/to/file.png} {image:https://picsum.photos/200/100} \| \| - \| Table \| Light syntax: {t \| Header 1 \| Header 2 \| \|----------\|----------\| \| Cell 1 \| Cell 2 \| \| Cell 3 \| Cell 4 \|} Explicit syntax: {table {tr {th Header 1} {th Header 2}} {tr {td Cell 1} {td Cell 2}} {tr {td Cell 3} {td Cell 4}}} \| Light syntax: Explicit syntax: \| - \| HTML \| {%html: \ Odoc language lack support for quotation! \ %} \| \| - \| Tags \| @since 4.08 Tags are explained in {{!page-odoc\_for\_authors.tags}this section}. \| Since 4.08. Tags are explained in this section . \| - $ cat markdown/test/Test.html + ## Section 1 + A very important type + ### Section 2 + A very important value + $ odoc markdown-generate test2.odocl -o markdown + $ odoc markdown-generate page-page.odocl -o markdown + ## Title + ### Subtitle + #### Referenceable title + See [Referenceable title](#my_id). + #### Styled + **bold** text, *italic* text, *emphasized* text + H2O and 1st + #### Link + Here is a link: [https://www.example.com](https://www.example.com). + You can also click [here](https://www.example.com). + #### References + See `Odoc_odoc.Compile.compile`. + See `Odoc_odoc.Compile.compile`. + See [this function from another library](). + See [this page from another package](). + See `{links`this section + } + for the syntax of references. + #### Lists + - First item + - Second item + 0. First ordered item + 1. Second numbered item + - First item + - Second item + - can also be used + 0. First numbered item + 1. Second numbered item + 2. can also be used + } + #### Code blocks + Inline `code`. + ```ocaml + let _ = "Block code" + ``` + ```text + Code block with {[inner code block syntax]} + ``` + ```python + [i+1 for i in xrange(2)] + ``` + } + #### Verbatim + ``` + verbatim text + ``` + #### Math + For inline math: \\sqrt 2. + For display math: + \\sqrt 2 + #### Images + ![./odoc\_logo\_placeholder.jpg]() + ![https://picsum.photos/200/100](https://picsum.photos/200/100) + #### Table + ##### Explicit syntax + \| Header 1 \| Header 2 \| + \| --- \| --- \| + \| Cell 1 \| Cell 2 \| + \| Cell 3 \| Cell 4 \| + } + ##### Light syntax + \| Header 1 \| Header 2 \| + \| --- \| --- \| + \| Cell 1 \| Cell 2 \| + \| Cell 3 \| Cell 4 \| + #### HTML + +
+ Odoc language lack support for quotation! +
+ + } + #### Tags + since 4\.08 + Tags are explained in this section. +$ cat markdown/test/Test.html diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli index 744d39185c..092f5371cd 100644 --- a/test/integration/markdown.t/test.mli +++ b/test/integration/markdown.t/test.mli @@ -1,307 +1,9 @@ -(** {0 Test} *) +(** {1 Section 1} *) -type t +type t = int +(** A very important type *) -(** {1 Test} *) +(** {2 Section 2} *) -(** Quick reference for the odoc language! - - {table - {tr {th } {th [odoc] syntax } {th Render as } } - {tr - {th Paragraphs } - {td - {@text[ - A first paragraph - - A second paragraph - ]} - } - {td - A first paragraph - - A second paragraph - } - } - {tr - {th {{!odoc_for_authors.sections}Headings} } - {td - {@text[ - {1 Title} - {2 Subtitle} - {3 Subsubtitle} - - {3:my_id Referenceable title} - - See {!my_id}. - ]} - - Standalone pages must start with a [0] heading: - - {@text[ - {0 Page big title} - ]} - } - {td - {%html:

Title

%} {%html:

Subtitle

%} - {%html:

Subsubtitle

%} - {%html:

Referenceable title

%} - - See {%html:Referenceable title%} - } - } - {tr - {th {{!odoc_for_authors.basics}Bold, italic and emphasis} } - {td - {@text[ - {b bold} text, {i italic} text, {e emphasized} text - ]} - } - {td {b bold} text, {i italic} text, {e emphasized} text } - } - {tr - {th {{!odoc_for_authors.basics}Subscripts and superscript} } - {td - {@text[ - H{_ 2}O and 1{^ st} - ]} - } - {td H{_ 2}O and 1{^ st} } - } - {tr - {th {{!odoc_for_authors.links_and_references}Link} } - {td - {@text[ - Here is a link: {:https://www.example.com}. - - You can also click {{:https://www.example.com}here}. - ]} - } - {td - Here is a link: {:https://www.example.com}. - - You can also click {{:https://www.example.com}here}. - } - } - {tr - {th {{!odoc_for_authors.links_and_references}References} } - {td - {@text[ - See {!Odoc_odoc.Compile.compile}. - - See {{!Odoc_odoc.Compile.compile}this function}. - - See {{!/fmt/Fmt.pf}this function from another library}. - - See {{!/cmdliner/tutorial}this page from another package}. - - See {{!odoc_for_authors.links_and_references}this section} for the syntax of references. - ]} - } - {td - See {!Odoc_odoc.Compile.compile}. - - See {{!Odoc_odoc.Compile.compile}this function}. - - See {{!/fmt/Fmt.pf}this function from another library}. - - See {{!/cmdliner/tutorial}this page from another package}. - - See {{!odoc_for_authors.links_and_references}this section} for the - syntax of references. - } - } - {tr - {th {{!odoc_for_authors.lists}Lists} } - {td - {@text[ - - First item - - Second item - - + First ordered item - + Second numbered item - - {ul - {- First item} - {- Second item} - {li can also be used}} - - {ol - {- First numbered item} - {- Second numbered item} - {li can also be used}} - ]} - } - {td - - First item - - Second item - - + First ordered item - + Second numbered item - - - First item - - Second item - - can also be used - - + First numbered item - + Second numbered item - + can also be used - } - } - {tr - {th {{!odoc_for_authors.code_blocks}Code Blocks} } - {td - {example@text[ - Inline [code]. - - {[ - let _ = "Block code" - ]} - - {foo@text[ - Code block with {[inner code block syntax]} - ]foo} - - {@python[ - [i+1 for i in xrange(2)] - ]} - ]example} - } - {td - Inline [code]. - - {[ - let _ = "Block code" - ]} - - {foo@text[ - Code block with {[inner code block syntax]} - ]foo} - - {@python[ - [i+1 for i in xrange(2)] - ]} - } - } - {tr - {th {{!odoc_for_authors.verbatim_blocks}Verbatim} } - {td - {example@text[ - {v verbatim text v} - ]example} - } - {td {v verbatim text v} } - } - {tr - {th {{!odoc_for_authors.math}Math} } - {td - {@text[ - For inline math: {m \sqrt 2}. - - For display math: - - {math \sqrt 2} - ]} - } - {td - For inline math: {m \sqrt 2}. - - For display math: - - {math \sqrt 2} - } - } - {tr - {th {{!odoc_for_authors.media}Images} } - {td - {@text[ - {image!path/to/file.png} - - {image:https://picsum.photos/200/100} - ]} - } - {td - {image!odoc_logo_placeholder.jpg} - - {image:https://picsum.photos/200/100} - } - } - {tr - {th {{!odoc_for_authors.tables}Table} } - {td - {@text[ - Light syntax: - - {t | Header 1 | Header 2 | - |----------|----------| - | Cell 1 | Cell 2 | - | Cell 3 | Cell 4 |} - - Explicit syntax: - - {table - {tr - {th Header 1} - {th Header 2}} - {tr - {td Cell 1} - {td Cell 2}} - {tr - {td Cell 3} - {td Cell 4}}} - ]} - } - {td - Light syntax: - - {t - | Header 1 | Header 2 | - |----------|----------| - | Cell 1 | Cell 2 | - | Cell 3 | Cell 4 | - } - - Explicit syntax: - - {table - {tr {th Header 1 } {th Header 2 } } - {tr {td Cell 1 } {td Cell 2 } } - {tr {td Cell 3 } {td Cell 4 } } - } - } - } - {tr - {th HTML } - {td - {example@text[ - {%html: -
- Odoc language lack support for quotation! -
- %} - ]example} - } - {td - {%html: -
- Odoc language lack support for quotation! -
- %} - } - } - {tr - {th {{!page-odoc_for_authors.tags}Tags} } - {td - {example@text[ - @since 4.08 - - Tags are explained in {{!page-odoc_for_authors.tags}this section}. - ]example} - } - {td - Since 4.08. - - Tags are explained in {{!page-odoc_for_authors.tags}this section}. - } - } - } *) +val v : t +(** A very important value *) From 7120383481878bf49b20f8cbba3a65b8b8661f56 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 19 Mar 2025 13:59:06 +0100 Subject: [PATCH 09/53] Add documentSrc support --- src/markdown2/generator.ml | 116 ++++++++++++++++++------------ test/integration/markdown.t/run.t | 24 ++----- 2 files changed, 73 insertions(+), 67 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 65a6aa50a6..82a717db86 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -14,6 +14,8 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +[@@@warning "-26-27"] + open Odoc_utils module HLink = Link @@ -415,68 +417,88 @@ and items ~config ~resolve l : Md.Block.t list = attr = _attr; anchor = _anchor; source_anchor = _source_anchor; - doc = _doc; + doc; content = { summary = _summary; status = _status; content = _content }; } :: rest -> - (* let doc = spec_doc_div ~config ~resolve doc in - let included_html = items content in - let a_class = - if List.length content = 0 then [ "odoc-include"; "shadowed-include" ] - else [ "odoc-include" ] - in *) - let content = [ Md.Block.empty ] in - (* let content = - let details ~open' = - let open' = if open' then [ Html.a_open () ] else [] in - let summary = - let extra_attr, extra_class, anchor_link = mk_anchor anchor in - let link_to_source = - mk_link_to_source ~config ~resolve source_anchor - in - let a = spec_class (attr @ extra_class) @ extra_attr in - Html.summary ~a @@ anchor_link @ link_to_source - @ source (inline ~config ~resolve) summary - in - let inner = - [ - Html.details ~a:open' summary - (included_html :> any Html.elt list); - ] - in - [ Html.div ~a:[ Html.a_class a_class ] (doc @ inner) ] - in - match status with - | `Inline -> doc @ included_html - | `Closed -> details ~open':false - | `Open -> details ~open':true - | `Default -> details ~open':true (* (Config.open_details config) *) - in *) + (* TODO: Test includes *) + let content = block ~config ~resolve doc in (continue_with [@tailcall]) rest content | Declaration { Item.attr = _attr; anchor = _anchor; source_anchor = _source_anchor; - content = _content; + content; doc; } :: rest -> - (* let extra_attr, extra_class, anchor_link = mk_anchor anchor in - let link_to_source = mk_link_to_source ~config ~resolve source_anchor in - let a = spec_class (attr @ extra_class) @ extra_attr in - let content = - anchor_link @ link_to_source @ documentedSrc ~config ~resolve content - in *) - let spec = block ~config ~resolve doc in - (* let spec = - let doc = spec_doc_div ~config ~resolve doc in - [ div ~a:[ Html.a_class [ "odoc-spec" ] ] (div ~a content :: doc) ] - in *) - (continue_with [@tailcall]) rest spec + let spec = documentedSrc ~config ~resolve content in + let doc = block ~config ~resolve doc in + let content = spec @ doc in + (continue_with [@tailcall]) rest content and items l = walk_items [] l in items l +and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = + let open DocumentedSrc in + let take_code l = + Doctree.Take.until l ~classify:(fun x -> + match (x : DocumentedSrc.one) with + | Code code -> Accum code + | Alternative (Expansion { summary; _ }) -> Accum summary + | _ -> Stop_and_keep) + in + let take_descr l = + Doctree.Take.until l ~classify:(function + | Documented { attrs; anchor; code; doc; markers } -> + Accum + [ { DocumentedSrc.attrs; anchor; code = `D code; doc; markers } ] + | Nested { attrs; anchor; code; doc; markers } -> + Accum + [ { DocumentedSrc.attrs; anchor; code = `N code; doc; markers } ] + | _ -> Stop_and_keep) + in + let rec to_markdown t : Md.Block.t list = + match t with + | [] -> [] + | (Code _ | Alternative _) :: _ -> + let code, _, rest = take_code t in + let inline_source = source (inline ~config ~resolve) code in + let inlines = Md.Inline.Inlines (inline_source, Md.meta) in + let block = + Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) + in + [ block ] @ to_markdown rest + | Subpage subp :: _ -> subpage ~config ~resolve subp + | (Documented _ | Nested _) :: _ -> + let l, _, rest = take_descr t in + let one { DocumentedSrc.attrs = _; anchor = _; code; doc; markers = _ } + = + let content = + match code with + | `D code -> + let inline_source = inline ~config ~resolve code in + let inlines = Md.Inline.Inlines (inline_source, Md.meta) in + let block = + Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) + in + [ block ] + | `N n -> to_markdown n + in + + let block_doc = block ~config ~resolve doc in + List.append content block_doc + in + let all_blocks = List.concat_map one l in + let rest_of_markdown = to_markdown rest in + all_blocks @ rest_of_markdown + in + to_markdown t + +and subpage ~config ~resolve (subp : Subpage.t) = + items ~config ~resolve subp.content.items + module Toc = struct open Odoc_document.Doctree open Types diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 75ce77900a..036d711637 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -1,12 +1,6 @@ $ ocamlc -c -bin-annot test.mli $ ocamlc -c -bin-annot test2.mli $ odoc compile --package test -I . page.mld - File "page.mld", line 33, characters 4-12: - Warning: '{{links}': bad markup. - Suggestion: did you mean '{!{links}' or '[{links]'? - File "page.mld", line 33, characters 24-25: - Warning: Unpaired '}' (end of markup). - Suggestion: try '\}'. File "page.mld", line 51, characters 24-25: Warning: Unpaired '}' (end of markup). Suggestion: try '\}'. @@ -22,17 +16,6 @@ File "page.mld", line 119, characters 0-11: Warning: Tags are not allowed in pages. $ odoc compile --package test test.cmti - $ ls - odoc_logo_placeholder.jpg - page-page.odoc - page.mld - test.cmi - test.cmti - test.mli - test.odoc - test2.cmi - test2.cmti - test2.mli $ odoc compile --package test -I . test2.cmti $ odoc link test.odoc $ odoc link test2.odoc @@ -45,10 +28,13 @@ Warning: Failed to resolve reference /test.v Path '/test' not found $ odoc markdown-generate test.odocl -o markdown ## Section 1 + type t = int A very important type ### Section 2 + val v : [t](#type-t) A very important value $ odoc markdown-generate test2.odocl -o markdown + val v : [Test.t](Test.html#type-t) $ odoc markdown-generate page-page.odocl -o markdown ## Title ### Subtitle @@ -65,9 +51,7 @@ See `Odoc_odoc.Compile.compile`. See [this function from another library](). See [this page from another package](). - See `{links`this section - } - for the syntax of references. + See [this section](#styled) for the syntax of references. #### Lists - First item - Second item From bceb1445158223fe79ba808e6325fbd1cc2c46a8 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 4 Apr 2025 10:47:19 +0200 Subject: [PATCH 10/53] Inline code blocks into one line --- src/markdown2/generator.ml | 33 +++++++++++++++++++++++---------- 1 file changed, 23 insertions(+), 10 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 82a717db86..838523cd86 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -14,7 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -[@@@warning "-26-27"] +[@@@warning "-26-27-32"] open Odoc_utils @@ -30,10 +30,10 @@ module Md = struct let meta = Cmarkit.Meta.none end -let source k (t : Source.t) = +let source fn (t : Source.t) = let rec token (x : Source.token) = match x with - | Elt i -> k i + | Elt i -> fn i | Tag (None, l) -> tokens l | Tag (Some _s, l) -> (* TODO: Implement tag with Some, what's the difference between Some and None? *) @@ -62,8 +62,10 @@ let rec inline_text_only (inline : Inline.t) : string list = List.concat_map (fun (i : Inline.one) -> match i.desc with + | Text "" -> [] | Text s -> [ s ] | Entity s -> [ s ] + | Linebreak -> [] | Styled (_, content) -> inline_text_only content | Link { content; _ } -> inline_text_only content | Source s -> source inline_text_only s @@ -125,7 +127,7 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = let inline_link = Md.Inline.Link.make link_inline link_reference in [ Md.Inline.Link (inline_link, Md.meta) ] | Source c -> - (* Markdown doesn't allow any complex node inside inline text, right now rendering only Inline.Text nodes, in the future we can render everything as strings *) + (* Markdown doesn't allow any complex node inside inline text, right now rendering only inline nodes, in the future we can render everything as strings *) let content = String.concat ~sep:"" (source inline_text_only c) in [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] | Math s -> @@ -463,11 +465,23 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = match t with | [] -> [] | (Code _ | Alternative _) :: _ -> - let code, _, rest = take_code t in - let inline_source = source (inline ~config ~resolve) code in - let inlines = Md.Inline.Inlines (inline_source, Md.meta) in + let code, header, rest = take_code t in + let info_string = + match header with + | Some header -> Some (header, Md.meta) + | None -> None + in + let inline_source = source inline_text_only code in + let code_block = [ (String.concat ~sep:"" inline_source, Md.meta) ] in + let fenced = + Md.Block.Code_block. + { indent = 0; opening_fence = ("", Md.meta); closing_fence = None } + in let block = - Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) + Md.Block.Code_block + ( Md.Block.Code_block.make ~layout:(`Fenced fenced) ?info_string + code_block, + Md.meta ) in [ block ] @ to_markdown rest | Subpage subp :: _ -> subpage ~config ~resolve subp @@ -491,8 +505,7 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = List.append content block_doc in let all_blocks = List.concat_map one l in - let rest_of_markdown = to_markdown rest in - all_blocks @ rest_of_markdown + all_blocks @ to_markdown rest in to_markdown t From c7851bdad63e67b3af6f3f72d26713b79ffd48a4 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 4 Apr 2025 13:20:25 +0200 Subject: [PATCH 11/53] Fix most printing issues on markdown --- src/markdown2/generator.ml | 106 +++++------ src/markdown2/generator.mli | 6 - src/markdown2/link.mli | 14 +- src/markdown2/markdown_page.ml | 258 ++------------------------ src/markdown2/markdown_page.mli | 6 - test/integration/markdown.t/array.mli | 39 ++++ test/integration/markdown.t/list.mli | 39 ++++ test/integration/markdown.t/page.mld | 20 +- test/integration/markdown.t/run.t | 88 ++++++--- 9 files changed, 214 insertions(+), 362 deletions(-) create mode 100644 test/integration/markdown.t/array.mli create mode 100644 test/integration/markdown.t/list.mli diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 838523cd86..812bf1cd13 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -32,12 +32,7 @@ end let source fn (t : Source.t) = let rec token (x : Source.token) = - match x with - | Elt i -> fn i - | Tag (None, l) -> tokens l - | Tag (Some _s, l) -> - (* TODO: Implement tag with Some, what's the difference between Some and None? *) - tokens l + match x with Elt i -> fn i | Tag (_, l) -> tokens l and tokens t = List.concat_map token t in tokens t @@ -54,17 +49,18 @@ and styled style ~emph_level:_ content = let emphasis = Md.Inline.Emphasis.make inlines_as_one_inline in [ Md.Inline.Emphasis (emphasis, Md.meta) ] | `Superscript | `Subscript -> - (* CommonMark doesn't have native support for superscript/subscript, - so we just include the content as inline directly *) + (* CommonMark doesn't have support for superscript/subscript, render the content as inline *) content -let rec inline_text_only (inline : Inline.t) : string list = +let entity = function "#45" -> "-" | "gt" -> ">" | e -> "&" ^ e ^ ";" + +let rec inline_text_only inline = List.concat_map (fun (i : Inline.one) -> match i.desc with | Text "" -> [] | Text s -> [ s ] - | Entity s -> [ s ] + | Entity s -> [ entity s ] | Linebreak -> [] | Styled (_, content) -> inline_text_only content | Link { content; _ } -> inline_text_only content @@ -88,12 +84,10 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = match t.desc with | Text s -> [ Md.Inline.Text (s, Md.meta) ] | Entity s -> - (* In Markdown, HTML entities are supported directly, so we can just output them as text *) + (* In CommonMark, HTML entities are supported directly, so we can just output them as text *) [ Md.Inline.Text (s, Md.meta) ] | Linebreak -> - (* In CommonMark, a hard line break can be represented by a backslash followed by a newline - or by two or more spaces at the end of a line. We'll use the hard break here. *) - (* We could use Thematic_break ? *) + (* In CommonMark, a hard line break can be represented by a backslash followed by a newline or by two or more spaces at the end of a line. We use a hard break *) let break = Md.Inline.Break.make `Hard in [ Md.Inline.Break (break, Md.meta) ] | Styled (style, c) -> @@ -108,8 +102,7 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = let link_reference = `Inline (link_definition, Md.meta) in let inline_link = Md.Inline.Link.make link_inline link_reference in [ Md.Inline.Link (inline_link, Md.meta) ] - | Link { target = Internal internal; content; tooltip = _ } -> - (* TODO: What's tooltip? *) + | Link { target = Internal internal; content; _ } -> let href = match internal with | Resolved uri -> @@ -117,7 +110,7 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = let url = Link.href ~config ~resolve uri in (url, Md.meta) | Unresolved -> - (* TODO: What's unresolved? A non-existing page/link? *) + (* TODO: What's unresolved? A non-existing page/link? Do we want to raise or empty? *) ("", Md.meta) in let inline_content = inline ~config ~emph_level ~resolve content in @@ -127,23 +120,28 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = let inline_link = Md.Inline.Link.make link_inline link_reference in [ Md.Inline.Link (inline_link, Md.meta) ] | Source c -> - (* Markdown doesn't allow any complex node inside inline text, right now rendering only inline nodes, in the future we can render everything as strings *) + (* CommonMark doesn't allow any complex node inside inline text, right now rendering inline nodes as text *) let content = String.concat ~sep:"" (source inline_text_only c) in [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] | Math s -> - (* Since CommonMark doesn't support Math's, we just treat it as text. - | Ext_math_block of Code_block.t node - {{!Cmarkit.ext_math_display}display math} *) - [ Md.Inline.Text (s, Md.meta) ] - | Raw_markup _ -> - (* TODO: Is there any way to trick this? *) - failwith "Markdown doesn't support raw markup in inline text" + (* Since CommonMark doesn't support Math's, we just treat it as code. Maybe could use Ext_math_block or Ext_math_display *) + [ Md.Inline.Code_span (Md.Inline.Code_span.of_string s, Md.meta) ] + | Raw_markup (target, content) -> ( + match Astring.String.Ascii.lowercase target with + | "html" -> + let block_lines = Md.Block_line.tight_list_of_string content in + [ Md.Inline.Raw_html (block_lines, Md.meta) ] + | another_lang -> + (* TODO: Is this correct? *) + let msg = + "Markdown only supports html blocks. There's a raw with " + ^ another_lang + in + failwith msg) in List.concat_map one l let heading ~config ~resolve (h : Heading.t) : Md.Block.t list = - (* TODO: Can I do something with the id? *) - let _id = h.label in let inlines = inline ~config ~resolve h.title in let content = Md.Inline.Inlines (inlines, Md.meta) in let heading = @@ -325,7 +323,7 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = (* We extract definition as inline, since it came as "Block". There seems to be no way (in Cmarkit) to make it inline *) let definition_inline = Md.Inline.Text - (String.concat ~sep:" " (block_text_only definition), Md.meta) + (String.concat ~sep:"" (block_text_only definition), Md.meta) in let space = Md.Inline.Text (" ", Md.meta) in let term_inline = @@ -335,7 +333,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = in List.concat_map item l | Verbatim s -> - (* TODO: Not entirely sure if this is right, in HTML is `mk_block Html.pre [ Html.txt s ]` *) let code_snippet = Md.Block.Code_block (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) @@ -352,19 +349,24 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = in [ code_snippet ] | Math s -> - let math_as_inline_text = Md.Inline.Text (s, Md.meta) in - let inlines = Md.Inline.Inlines ([ math_as_inline_text ], Md.meta) in - let paragraph_block = - Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) + (* Since CommonMark doesn't support Math's, we just treat it as code. Maybe could use Ext_math_block or Ext_math_display *) + let block = + Md.Block.Code_block + (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) in - [ paragraph_block ] + [ block ] | Raw_markup (target, content) -> ( - (* TODO: Is this correct? *) match Astring.String.Ascii.lowercase target with | "html" -> let block_lines = Md.Block_line.list_of_string content in [ Md.Block.Html_block (block_lines, Md.meta) ] - | _ -> []) + | another_lang -> + (* TODO: Is this correct? *) + let msg = + "Markdown only supports html blocks. There's a raw with " + ^ another_lang + in + failwith msg) | Audio (_target, _alt) -> (* TODO: Raise a decent error here? Only saw assert false :( *) failwith "Audio isn't supported in markdown" @@ -423,7 +425,6 @@ and items ~config ~resolve l : Md.Block.t list = content = { summary = _summary; status = _status; content = _content }; } :: rest -> - (* TODO: Test includes *) let content = block ~config ~resolve doc in (continue_with [@tailcall]) rest content | Declaration @@ -473,15 +474,9 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = in let inline_source = source inline_text_only code in let code_block = [ (String.concat ~sep:"" inline_source, Md.meta) ] in - let fenced = - Md.Block.Code_block. - { indent = 0; opening_fence = ("", Md.meta); closing_fence = None } - in let block = Md.Block.Code_block - ( Md.Block.Code_block.make ~layout:(`Fenced fenced) ?info_string - code_block, - Md.meta ) + (Md.Block.Code_block.make ?info_string code_block, Md.meta) in [ block ] @ to_markdown rest | Subpage subp :: _ -> subpage ~config ~resolve subp @@ -704,23 +699,13 @@ module Page = struct ~breadcrumbs ~url ~uses_katex doc subpages and source_page ~config ~sidebar sp = + (* TODO: I'm not enturely sure when this is called *) let { Source_page.url; contents = _ } = sp in let _resolve = Link.Current sp.url in let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~sidebar ~url in - let sidebar = - (* match sidebar with - | None -> None - | Some sidebar -> - let sidebar = Odoc_document.Sidebar.to_block sidebar url in - (Some (block ~config ~resolve sidebar) :> any Html.elt list option) *) - None - in + let sidebar = None in let title = url.Url.Path.name and doc = [ Md.Block.empty ] in - (* and doc = Markdown_source.html_of_doc ~config ~resolve contents in *) - let header = - (* items ~config ~resolve (Doctree.PageTitle.render_src_title sp) *) - [] - in + let header = [] in Markdown_page.make_src ~breadcrumbs ~header ~config ~url ~sidebar title doc end @@ -732,13 +717,6 @@ let render ~(config : Config.t) ~sidebar = function let filepath ~config url = Link.Path.as_filename ~config url -(* TODO: Where is this beeing called? *) -let doc ~config ~xref_base_uri b = - let resolve = Link.Base xref_base_uri in - let block = block ~config ~resolve b in - let root_block = Md.Block.Blocks (block, Md.meta) in - Cmarkit.Doc.make root_block - let inline ~config ~xref_base_uri b = let resolve = Link.Base xref_base_uri in inline ~config ~resolve b diff --git a/src/markdown2/generator.mli b/src/markdown2/generator.mli index afc3b57d6f..5415581fec 100644 --- a/src/markdown2/generator.mli +++ b/src/markdown2/generator.mli @@ -12,12 +12,6 @@ val items : Odoc_document.Types.Item.t list -> Cmarkit.Block.t list -val doc : - config:Config.t -> - xref_base_uri:string -> - Odoc_document.Types.Block.t -> - Cmarkit.Doc.t - val inline : config:Config.t -> xref_base_uri:string -> diff --git a/src/markdown2/link.mli b/src/markdown2/link.mli index 3bff6dae3d..0090330505 100644 --- a/src/markdown2/link.mli +++ b/src/markdown2/link.mli @@ -1,15 +1,13 @@ -(** HTML-specific interpretation of {!Odoc_document.Url} *) +(** Markdown-specific interpretation of {!Odoc_document.Url} *) -module Url = Odoc_document.Url +type resolve = Current of Odoc_document.Url.Path.t | Base of string -type resolve = Current of Url.Path.t | Base of string - -val href : config:Config.t -> resolve:resolve -> Url.t -> string +val href : config:Config.t -> resolve:resolve -> Odoc_document.Url.t -> string module Path : sig - val is_leaf_page : Url.Path.t -> bool + val is_leaf_page : Odoc_document.Url.Path.t -> bool - val for_printing : Url.Path.t -> string list + val for_printing : Odoc_document.Url.Path.t -> string list - val as_filename : config:Config.t -> Url.Path.t -> Fpath.t + val as_filename : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t end diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index ca63f1a835..f90043a4fc 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -14,256 +14,26 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -[@@@warning "-27-32"] - -open Odoc_utils - module Url = Odoc_document.Url -module Html = Tyxml.Html - -let html_of_toc toc = - let open Types in - let rec section (section : toc) = - let link = Html.a ~a:[ Html.a_href section.href ] section.title in - match section.children with [] -> [ link ] | cs -> [ link; sections cs ] - and sections the_sections = - the_sections - |> List.map (fun the_section -> Html.li (section the_section)) - |> Html.ul - in - match toc with [] -> [] | _ -> [ sections toc ] - -let sidebars ~global_toc ~local_toc = - let local_toc = - match local_toc with - | [] -> [] - | _ :: _ -> - [ - Html.nav - ~a:[ Html.a_class [ "odoc-toc"; "odoc-local-toc" ] ] - (html_of_toc local_toc); - ] - in - let global_toc = - match global_toc with - | None -> [] - | Some c -> - [ Html.nav ~a:[ Html.a_class [ "odoc-toc"; "odoc-global-toc" ] ] c ] - in - match local_toc @ global_toc with - | [] -> [] - | tocs -> [ Html.div ~a:[ Html.a_class [ "odoc-tocs" ] ] tocs ] - -let html_of_breadcrumbs (breadcrumbs : Types.breadcrumbs) = - let make_navigation ~up_url rest = - let up = - match up_url with - | None -> [] - | Some up_url -> - [ Html.a ~a:[ Html.a_href up_url ] [ Html.txt "Up" ]; Html.txt " – " ] - in - [ Html.nav ~a:[ Html.a_class [ "odoc-nav" ] ] (up @ rest) ] - in - let space = Html.txt " " in - let sep = [ space; Html.entity "#x00BB"; space ] in - let html = - (* Create breadcrumbs *) - List.concat_map_sep ~sep - ~f:(fun (breadcrumb : Types.breadcrumb) -> - match breadcrumb.href with - | Some href -> - [ - [ - Html.a - ~a:[ Html.a_href href ] - (breadcrumb.name - :> Html_types.flow5_without_interactive Html.elt list); - ]; - ] - | None -> - [ (breadcrumb.name :> Html_types.nav_content_fun Html.elt list) ]) - breadcrumbs.parents - |> List.flatten - in - let current_name :> Html_types.nav_content_fun Html.elt list = - breadcrumbs.current.name - in - let rest = - if List.is_empty breadcrumbs.parents then current_name - else html @ sep @ current_name - in - make_navigation ~up_url:breadcrumbs.up_url - (rest :> [< Html_types.nav_content_fun > `A `PCDATA `Wbr ] Html.elt list) - -(* let file_uri ~config ~url (base : Types.uri) file = - match base with - | Types.Absolute uri -> uri ^ "/" ^ file - | Relative uri -> - let page = Url.Path.{ kind = `File; parent = uri; name = file } in - Link.href ~config ~resolve:(Current url) (Url.from_path page) - *) - -let page_creator ~config ~url ~uses_katex ~global_toc header breadcrumbs - local_toc content = - (* let theme_uri = None in - let support_uri = None in - let search_uris = [] in - let path = Link.Path.for_printing url in - - let head : Html_types.head Html.elt = - let title_string = - Printf.sprintf "%s (%s)" url.name (String.concat ~sep:"." path) - in - let file_uri = file_uri ~config ~url in - let search_uri uri = - match uri with - | Types.Absolute uri -> uri - | Relative uri -> - Link.href ~config ~resolve:(Current url) (Url.from_path uri) - in - let search_scripts = - match search_uris with - | [] -> [] - | _ -> - let search_urls = List.map search_uri search_uris in - let search_urls = - let search_url name = Printf.sprintf "'%s'" name in - let search_urls = List.map search_url search_urls in - "[" ^ String.concat ~sep:"," search_urls ^ "]" - in - (* The names of the search scripts are put into a js variable. Then - the code in [odoc_search.js] load them into a webworker. *) - [ - Html.script ~a:[] - (Html.txt - (Format.asprintf - {|let base_url = '%s'; -let search_urls = %s; -|} - (let page = - Url.Path.{ kind = `File; parent = None; name = "" } - in - Link.href ~config ~resolve:(Current url) - (Url.from_path page)) - search_urls)); - Html.script - ~a: - [ - Html.a_src (file_uri support_uri "odoc_search.js"); - Html.a_defer (); - ] - (Html.txt ""); - ] - in - let meta_elements = - let highlightjs_meta = - let highlight_js_uri = file_uri support_uri "highlight.pack.js" in - [ - Html.script ~a:[ Html.a_src highlight_js_uri ] (Html.txt ""); - Html.script (Html.txt "hljs.initHighlightingOnLoad();"); - ] - in - let katex_meta = - if uses_katex then - let katex_css_uri = file_uri theme_uri "katex.min.css" in - let katex_js_uri = file_uri support_uri "katex.min.js" in - [ - Html.link ~rel:[ `Stylesheet ] ~href:katex_css_uri (); - Html.script ~a:[ Html.a_src katex_js_uri ] (Html.txt ""); - Html.script - (Html.cdata_script - {| - document.addEventListener("DOMContentLoaded", function () { - var elements = Array.from(document.getElementsByClassName("odoc-katex-math")); - for (var i = 0; i < elements.length; i++) { - var el = elements[i]; - var content = el.textContent; - var new_el = document.createElement("span"); - new_el.setAttribute("class", "odoc-katex-math-rendered"); - var display = el.classList.contains("display"); - katex.render(content, new_el, { throwOnError: false, displayMode: display }); - el.replaceWith(new_el); - } - }); - |}); - ] - else [] - in - default_meta_elements ~config ~url @ highlightjs_meta @ katex_meta - in - let meta_elements = meta_elements @ search_scripts in - Html.head (Html.title (Html.txt title_string)) meta_elements - in - let search_bar = - match search_uris with - | [] -> [] - | _ -> - [ Html.div ~a:[ Html.a_class [ "odoc-search" ] ] [ html_of_search () ] ] - in +let page_creator content = + fun _ppf -> + let renderer = Cmarkit_commonmark.renderer () in + Format.printf "%s" (Cmarkit_renderer.doc_to_string renderer content) - let body = - html_of_breadcrumbs breadcrumbs - @ search_bar - @ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ] - @ sidebars ~global_toc ~local_toc - @ [ Html.div ~a:[ Html.a_class [ "odoc-content" ] ] content ] - in - - let htmlpp = Html.pp () in - let html = Html.html head (Html.body ~a:[ Html.a_class [ "odoc" ] ] body) in - let content ppf = - htmlpp ppf html; - (* Tyxml's pp doesn't output a newline a the end, so we force one *) - Format.pp_force_newline ppf () - in - content *) - let content ppf = - let renderer = Cmarkit_commonmark.renderer () in - Format.printf "%s" (Cmarkit_renderer.doc_to_string renderer content) - in - content - -let make ~config ~url ~header ~breadcrumbs ~sidebar ~toc ~uses_katex content - children = +let make ~config ~url ~header:_ ~breadcrumbs:_ ~sidebar:_ ~toc:_ ~uses_katex:_ + content children = let filename = Link.Path.as_filename ~config url in - let content = - page_creator ~config ~url ~uses_katex ~global_toc:sidebar header breadcrumbs - toc content - in + let content = page_creator content in { Odoc_document.Renderer.filename; content; children; path = url } -let path_of_module_of_source ppf url = - match url.Url.Path.parent with - | Some parent -> - let path = Link.Path.for_printing parent in - Format.fprintf ppf " (%s)" (String.concat ~sep:"." path) - | None -> () - -let src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar name content = - (* let head : Html_types.head Html.elt = - let title_string = - Format.asprintf "Source: %s%a" name path_of_module_of_source url - in - let meta_elements = [] in - Html.head (Html.title (Html.txt title_string)) meta_elements - in - let body = - html_of_breadcrumbs breadcrumbs - @ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ] - @ sidebars ~global_toc:sidebar ~local_toc:[] - @ content - in *) - let content ppf = - Format.fprintf ppf "%s" "TODO!"; - (* Tyxml's pp doesn't output a newline a the end, so we force one *) - Format.pp_force_newline ppf () - in - content +let src_page_creator _name _content = + fun ppf -> + (* TODO: Not exactly sure when this is called *) + Format.fprintf ppf "%s" "TODO?"; + Format.pp_force_newline ppf () -let make_src ~config ~url ~breadcrumbs ~header ~sidebar title content = +let make_src ~config ~url ~breadcrumbs:_ ~header:_ ~sidebar:_ title content = let filename = Link.Path.as_filename ~config url in - let content = - src_page_creator ~breadcrumbs ~config ~url ~header ~sidebar title content - in + let content = src_page_creator title content in { Odoc_document.Renderer.filename; content; children = []; path = url } diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index f18633e11b..814f106243 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -29,9 +29,6 @@ val make : Cmarkit.Doc.t -> Odoc_document.Renderer.page list -> Odoc_document.Renderer.page -(** [make ?theme_uri (body, children)] calls "the page creator" to turn [body] - into an [[ `Html ] elt]. If [theme_uri] is provided, it will be used to - locate the theme files, otherwise the HTML output directory is used. *) val make_src : config:Config.t -> @@ -42,6 +39,3 @@ val make_src : string -> Cmarkit.Block.t list -> Odoc_document.Renderer.page -(** [make ?theme_uri (body, children)] calls "the page creator" to turn [body] - into an [[ `Html ] elt]. If [theme_uri] is provided, it will be used to - locate the theme files, otherwise the HTML output directory is used. *) diff --git a/test/integration/markdown.t/array.mli b/test/integration/markdown.t/array.mli new file mode 100644 index 0000000000..8613eda85f --- /dev/null +++ b/test/integration/markdown.t/array.mli @@ -0,0 +1,39 @@ +(** {0 List} + + Utilities for List data type. + + This module is compatible with original ocaml stdlib. In general, all + functions comes with the original stdlib also applies to this collection, + however, this module provides faster and stack safer utilities *) + +type 'a t = 'a list +(** ['a t] is compatible with built-in [list] type *) + +(** {2 length} *) + +val make : 'a t -> int +(** [length xs] + + @return the length of the list [xs] *) + +(** {2 size} *) + +val size : 'a t -> int +(** {b See} {!length} *) + +(** {2 head} *) + +val head : 'a t -> 'a option +(** [head xs] returns [None] if [xs] is the empty list, otherwise it returns + [Some value] where [value] is the first element in the list. + {[ + head [] = None;; + head [ 1; 2; 3 ] = Some 1 + ]} *) + +val headExn : 'a t -> 'a +(** [headExn xs] + + {b See} {!head} + + {b raise} an exception if [xs] is empty *) diff --git a/test/integration/markdown.t/list.mli b/test/integration/markdown.t/list.mli new file mode 100644 index 0000000000..8613eda85f --- /dev/null +++ b/test/integration/markdown.t/list.mli @@ -0,0 +1,39 @@ +(** {0 List} + + Utilities for List data type. + + This module is compatible with original ocaml stdlib. In general, all + functions comes with the original stdlib also applies to this collection, + however, this module provides faster and stack safer utilities *) + +type 'a t = 'a list +(** ['a t] is compatible with built-in [list] type *) + +(** {2 length} *) + +val make : 'a t -> int +(** [length xs] + + @return the length of the list [xs] *) + +(** {2 size} *) + +val size : 'a t -> int +(** {b See} {!length} *) + +(** {2 head} *) + +val head : 'a t -> 'a option +(** [head xs] returns [None] if [xs] is the empty list, otherwise it returns + [Some value] where [value] is the first element in the list. + {[ + head [] = None;; + head [ 1; 2; 3 ] = Some 1 + ]} *) + +val headExn : 'a t -> 'a +(** [headExn xs] + + {b See} {!head} + + {b raise} an exception if [xs] is empty *) diff --git a/test/integration/markdown.t/page.mld b/test/integration/markdown.t/page.mld index d5ce3225c0..f7c221202f 100644 --- a/test/integration/markdown.t/page.mld +++ b/test/integration/markdown.t/page.mld @@ -48,8 +48,7 @@ See {{!styled}this section} for the syntax of references. {ol {- First numbered item} {- Second numbered item} - {li can also be used}}} - + {li can also be used}} {3 Code blocks} @@ -65,7 +64,7 @@ Code block with {[inner code block syntax]} {@python[ [i+1 for i in xrange(2)] -]}} +]} {3 Verbatim} @@ -97,7 +96,7 @@ For display math: {td Cell 2}} {tr {td Cell 3} - {td Cell 4}}}]}} + {td Cell 4}}}]} {4 Light syntax} @@ -108,11 +107,16 @@ For display math: {3 HTML} +This is a strong tag: {%html: Odoc language lack support for quotation! +%} + {%html: -
- Odoc language lack support for quotation! -
-%}} +
+
+ Odoc language lack support for quotation! +
+
+%} {3 Tags} diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 036d711637..0d851df853 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -1,26 +1,21 @@ $ ocamlc -c -bin-annot test.mli $ ocamlc -c -bin-annot test2.mli + $ ocamlc -c -bin-annot list.mli $ odoc compile --package test -I . page.mld - File "page.mld", line 51, characters 24-25: - Warning: Unpaired '}' (end of markup). - Suggestion: try '\}'. - File "page.mld", line 68, characters 2-3: - Warning: Unpaired '}' (end of markup). - Suggestion: try '\}'. - File "page.mld", line 100, characters 19-20: - Warning: Unpaired '}' (end of markup). - Suggestion: try '\}'. - File "page.mld", line 115, characters 2-3: - Warning: Unpaired '}' (end of markup). - Suggestion: try '\}'. - File "page.mld", line 119, characters 0-11: + File "page.mld", line 123, characters 0-11: Warning: Tags are not allowed in pages. $ odoc compile --package test test.cmti $ odoc compile --package test -I . test2.cmti + $ odoc compile --package list -I . list.cmti + File "list.mli", line 1, characters 4-12: + Warning: '{0': heading level should be lower than top heading level '0'. $ odoc link test.odoc $ odoc link test2.odoc + $ odoc link list.odoc + File "list.mli", line 37, characters 12-19: + Warning: Reference to 'head' is ambiguous. Please specify its kind: section-head, val-head. $ odoc link page-page.odoc - File "page.mld", line 84, characters 0-33: + File "page.mld", line 83, characters 0-33: Warning: Failed to resolve reference ./odoc_logo_placeholder.jpg Path 'odoc_logo_placeholder.jpg' not found File "page.mld", line 31, characters 4-49: Warning: Failed to resolve reference ./test.mli Path 'test' not found @@ -28,13 +23,19 @@ Warning: Failed to resolve reference /test.v Path '/test' not found $ odoc markdown-generate test.odocl -o markdown ## Section 1 + ``` type t = int + ``` A very important type ### Section 2 - val v : [t](#type-t) + ``` + val v : t + ``` A very important value $ odoc markdown-generate test2.odocl -o markdown - val v : [Test.t](Test.html#type-t) + ``` + val v : Test.t + ``` $ odoc markdown-generate page-page.odocl -o markdown ## Title ### Subtitle @@ -63,7 +64,6 @@ 0. First numbered item 1. Second numbered item 2. can also be used - } #### Code blocks Inline `code`. ```ocaml @@ -75,15 +75,16 @@ ```python [i+1 for i in xrange(2)] ``` - } #### Verbatim ``` verbatim text ``` #### Math - For inline math: \\sqrt 2. + For inline math: `\sqrt 2`. For display math: - \\sqrt 2 + ``` + \sqrt 2 + ``` #### Images ![./odoc\_logo\_placeholder.jpg]() ![https://picsum.photos/200/100](https://picsum.photos/200/100) @@ -93,20 +94,55 @@ \| --- \| --- \| \| Cell 1 \| Cell 2 \| \| Cell 3 \| Cell 4 \| - } ##### Light syntax \| Header 1 \| Header 2 \| \| --- \| --- \| \| Cell 1 \| Cell 2 \| \| Cell 3 \| Cell 4 \| #### HTML + This is a strong tag: Odoc language lack support for quotation! + -
- Odoc language lack support for quotation! -
+
+
+ Odoc language lack support for quotation! +
+
- } #### Tags since 4\.08 Tags are explained in this section. -$ cat markdown/test/Test.html + $ odoc markdown-generate list.odocl -o markdown + # List + Utilities for List data type. + This module is compatible with original ocaml stdlib. In general, all functions comes with the original stdlib also applies to this collection, however, this module provides faster and stack safer utilities + ``` + type 'a t = 'a list + ``` + `'a t` is compatible with built-in `list` type + ### length + ``` + val make : 'a t -> int + ``` + `length xs` + returns the length of the list xs + ### size + ``` + val size : 'a t -> int + ``` + **See** [length](#length) + ### head + ``` + val head : 'a t -> 'a option + ``` + `head xs` returns `None` if `xs` is the empty list, otherwise it returns `Some value` where `value` is the first element in the list. + ```ocaml + head [] = None;; + head [ 1; 2; 3 ] = Some 1 + ``` + ``` + val headExn : 'a t -> 'a + ``` + `headExn xs` + **See** [`head`](#val-head) + **raise** an exception if `xs` is empty From dc4c53d56b98ff9299add56edfdd441aba1b0d9f Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 4 Apr 2025 20:24:31 +0200 Subject: [PATCH 12/53] Fix markdown links --- src/markdown2/link.ml | 21 ++--- src/markdown2/markdown_page.ml | 17 ++-- src/odoc/bin/main.ml | 2 +- test/integration/markdown.t/run.t | 118 ++------------------------- test/integration/markdown.t/test.mli | 6 ++ 5 files changed, 27 insertions(+), 137 deletions(-) diff --git a/src/markdown2/link.ml b/src/markdown2/link.ml index f3c72bb559..85939ac359 100644 --- a/src/markdown2/link.ml +++ b/src/markdown2/link.ml @@ -42,13 +42,13 @@ module Path = struct let dir = List.map segment_to_string dir in let file = match file with - | [] -> "index.html" - | [ (`LeafPage, name) ] -> name ^ ".html" + | [] -> "index.md" + | [ (`LeafPage, name) ] -> name ^ ".md" | [ (`File, name) ] -> name - | [ (`SourcePage, name) ] -> name ^ ".html" + | [ (`SourcePage, name) ] -> name ^ ".md" | xs -> (* assert (Config.flat config); *) - String.concat "-" (List.map segment_to_string xs) ^ ".html" + String.concat "-" (List.map segment_to_string xs) ^ ".md" in (dir, file) @@ -89,7 +89,6 @@ let href ~config ~resolve t = let dir, file = Path.get_dir_and_file ~config path in dir @ [ file ] in - let current_from_common_ancestor, target_from_common_ancestor = drop_shared_prefix current_loc target_loc in @@ -110,16 +109,6 @@ let href ~config ~resolve t = List.map (fun _ -> "..") (List.tl l) @ target_from_common_ancestor in - let remove_index_html l = - match List.rev l with - | "index.html" :: rest -> List.rev ("" :: rest) - | _ -> l - in - let relative_target = - if (* Config.semantic_uris config *) true then - remove_index_html relative_target - else relative_target - in match (relative_target, anchor) with | [], "" -> "#" - | page, _ -> add_anchor @@ String.concat "/" page)) + | page, _ -> "./" ^ add_anchor @@ String.concat "/" page)) diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index f90043a4fc..e4c620e0f6 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -16,10 +16,10 @@ module Url = Odoc_document.Url -let page_creator content = - fun _ppf -> +let page_creator doc = + fun (ppf : Format.formatter) -> let renderer = Cmarkit_commonmark.renderer () in - Format.printf "%s" (Cmarkit_renderer.doc_to_string renderer content) + Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) let make ~config ~url ~header:_ ~breadcrumbs:_ ~sidebar:_ ~toc:_ ~uses_katex:_ content children = @@ -27,11 +27,12 @@ let make ~config ~url ~header:_ ~breadcrumbs:_ ~sidebar:_ ~toc:_ ~uses_katex:_ let content = page_creator content in { Odoc_document.Renderer.filename; content; children; path = url } -let src_page_creator _name _content = - fun ppf -> - (* TODO: Not exactly sure when this is called *) - Format.fprintf ppf "%s" "TODO?"; - Format.pp_force_newline ppf () +let src_page_creator _name (block_list : Cmarkit.Block.t list) = + fun (ppf : Format.formatter) -> + let renderer = Cmarkit_commonmark.renderer () in + let root_block = Cmarkit.Block.Blocks (block_list, Cmarkit.Meta.none) in + let doc = Cmarkit.Doc.make root_block in + Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) let make_src ~config ~url ~breadcrumbs:_ ~header:_ ~sidebar:_ title content = let filename = Link.Path.as_filename ~config url in diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 8e9f8fa452..9d49aee177 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1722,7 +1722,7 @@ let () = Odoc_html.generate ~docs:section_pipeline; Odoc_html.generate_source ~docs:section_pipeline; Odoc_markdown_cmd.generate ~docs:section_pipeline; - (* Odoc_markdown_cmd.generate_source ~docs:section_pipeline; *) + (* TODO: Do this Odoc_markdown_cmd.generate_source ~docs:section_pipeline; *) Odoc_html.generate_asset ~docs:section_pipeline; Support_files_command.(cmd, info ~docs:section_pipeline); Compile_impl.(cmd, info ~docs:section_pipeline); diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 0d851df853..84a5053873 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -22,6 +22,11 @@ File "page.mld", line 29, characters 4-50: Warning: Failed to resolve reference /test.v Path '/test' not found $ odoc markdown-generate test.odocl -o markdown + $ odoc markdown-generate test2.odocl -o markdown + $ odoc markdown-generate page-page.odocl -o markdown + $ odoc markdown-generate list.odocl -o markdown + + $ cat markdown/test/Test.md ## Section 1 ``` type t = int @@ -32,117 +37,6 @@ val v : t ``` A very important value - $ odoc markdown-generate test2.odocl -o markdown - ``` - val v : Test.t - ``` - $ odoc markdown-generate page-page.odocl -o markdown - ## Title - ### Subtitle - #### Referenceable title - See [Referenceable title](#my_id). - #### Styled - **bold** text, *italic* text, *emphasized* text - H2O and 1st - #### Link - Here is a link: [https://www.example.com](https://www.example.com). - You can also click [here](https://www.example.com). - #### References - See `Odoc_odoc.Compile.compile`. - See `Odoc_odoc.Compile.compile`. - See [this function from another library](). - See [this page from another package](). - See [this section](#styled) for the syntax of references. - #### Lists - - First item - - Second item - 0. First ordered item - 1. Second numbered item - - First item - - Second item - - can also be used - 0. First numbered item - 1. Second numbered item - 2. can also be used - #### Code blocks - Inline `code`. - ```ocaml - let _ = "Block code" - ``` - ```text - Code block with {[inner code block syntax]} - ``` - ```python - [i+1 for i in xrange(2)] - ``` - #### Verbatim - ``` - verbatim text - ``` - #### Math - For inline math: `\sqrt 2`. - For display math: - ``` - \sqrt 2 - ``` - #### Images - ![./odoc\_logo\_placeholder.jpg]() - ![https://picsum.photos/200/100](https://picsum.photos/200/100) - #### Table - ##### Explicit syntax - \| Header 1 \| Header 2 \| - \| --- \| --- \| - \| Cell 1 \| Cell 2 \| - \| Cell 3 \| Cell 4 \| - ##### Light syntax - \| Header 1 \| Header 2 \| - \| --- \| --- \| - \| Cell 1 \| Cell 2 \| - \| Cell 3 \| Cell 4 \| - #### HTML - This is a strong tag: Odoc language lack support for quotation! - - -
-
- Odoc language lack support for quotation! -
-
- - #### Tags - since 4\.08 - Tags are explained in this section. - $ odoc markdown-generate list.odocl -o markdown - # List - Utilities for List data type. - This module is compatible with original ocaml stdlib. In general, all functions comes with the original stdlib also applies to this collection, however, this module provides faster and stack safer utilities - ``` - type 'a t = 'a list - ``` - `'a t` is compatible with built-in `list` type - ### length - ``` - val make : 'a t -> int - ``` - `length xs` - returns the length of the list xs - ### size - ``` - val size : 'a t -> int - ``` - **See** [length](#length) - ### head - ``` - val head : 'a t -> 'a option - ``` - `head xs` returns `None` if `xs` is the empty list, otherwise it returns `Some value` where `value` is the first element in the list. - ```ocaml - head [] = None;; - head [ 1; 2; 3 ] = Some 1 - ``` ``` - val headExn : 'a t -> 'a + module List : sig ... end ``` - `headExn xs` - **See** [`head`](#val-head) - **raise** an exception if `xs` is empty diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli index 092f5371cd..6d1c508a65 100644 --- a/test/integration/markdown.t/test.mli +++ b/test/integration/markdown.t/test.mli @@ -7,3 +7,9 @@ type t = int val v : t (** A very important value *) + +module List : sig + type 'a t = 'a list + val head : 'a t -> 'a option + val headExn : 'a t -> 'a +end From bdabf64a2ac3ee6769d3c5b5bf953aa83e8388f3 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 4 Apr 2025 20:30:31 +0200 Subject: [PATCH 13/53] Add library for in tests --- .../integration/markdown-with-belt.t/Belt.mli | 105 ++++++++++++++++++ .../markdown-with-belt.t/Belt_Id.mli | 10 ++ test/integration/markdown-with-belt.t/run.t | 26 +++++ 3 files changed, 141 insertions(+) create mode 100644 test/integration/markdown-with-belt.t/Belt.mli create mode 100644 test/integration/markdown-with-belt.t/Belt_Id.mli create mode 100644 test/integration/markdown-with-belt.t/run.t diff --git a/test/integration/markdown-with-belt.t/Belt.mli b/test/integration/markdown-with-belt.t/Belt.mli new file mode 100644 index 0000000000..1887429f59 --- /dev/null +++ b/test/integration/markdown-with-belt.t/Belt.mli @@ -0,0 +1,105 @@ +(** A stdlib shipped with Melange + + This stdlib is still in {i beta} but we encourage you to try it out and give + us feedback. + + {b Motivation} + + The motivation for creating such library is to provide Melange users a + better end-to-end user experience, since the original OCaml stdlib was not + written with JS in mind. Below is a list of areas this lib aims to improve: + + Consistency in name convention: camlCase, and arguments order + + Exception thrown functions are all suffixed with {i Exn}, e.g, {i getExn} + + Better performance and smaller code size running on JS platform + + {b Name Convention} + + For higher order functions, it will be suffixed {b U} if it takes uncurried + callback. + + {[ + val forEach : 'a t -> ('a -> unit) -> unit + val forEachU : 'a t -> ('a -> unit [\@u]) -> unit + ]} + + In general, uncurried version will be faster, but it may be less familiar to + people who have a background in functional programming. + + {b A special encoding for collection safety} + + When we create a collection library for a custom data type we need a way to + provide a comparator function. Take {i Set} for example, suppose its element + type is a pair of ints, it needs a custom {i compare} function that takes + two tuples and returns their order. The {i Set} could not just be typed as + [ Set.t (int * int) ], its customized {i compare} function needs to manifest + itself in the signature, otherwise, if the user creates another customized + {i compare} function, the two collection could mix which would result in + runtime error. + + The original OCaml stdlib solved the problem using {i functor} which creates + a big closure at runtime and makes dead code elimination much harder. We use + a phantom type to solve the problem: + + {[ + module Comparable1 = Belt.Id.MakeComparable (struct + type t = int * int + let cmp (a0, a1) (b0, b1) = + match Pervasives.compare a0 b0 with + | 0 -> Pervasives.compare a1 b1 + | c -> c + end) + + let mySet1 = Belt.Set.make ~id:(module Comparable1) + + module Comparable2 = Belt.Id.MakeComparable (struct + type t = int * int + let cmp (a0, a1) (b0, b1) = + match Pervasives.compare a0 b0 with + | 0 -> Pervasives.compare a1 b1 + | c -> c + end) + + let mySet2 = Belt.Set.make ~id:(module Comparable2) + ]} + + Here, the compiler would infer [mySet1] and [mySet2] having different type, + so e.g. a `merge` operation that tries to merge these two sets will + correctly fail. + + {[ + val mySet1 : (int * int, Comparable1.identity) t + val mySet2 : (int * int, Comparable2.identity) t + ]} + + [Comparable1.identity] and [Comparable2.identity] are not the same using our + encoding scheme. + + {b Collection Hierarchy} + + In general, we provide a generic collection module, but also create + specialized modules for commonly used data type. Take {i Belt.Set} for + example, we provide: + + {[ + Belt.Set + Belt.Set.Int + Belt.Set.String + ]} + + The specialized modules {i Belt.Set.Int}, {i Belt.Set.String} are in general + more efficient. + + Currently, both {i Belt_Set} and {i Belt.Set} are accessible to users for + some technical reasons, we {b strongly recommend} users stick to qualified + import, {i Belt.Set}, we may hide the internal, {i i.e}, {i Belt_Set} in the + future *) + +module Id = Belt_Id + +(** {!Belt.Id} + + Provide utilities to create identified comparators or hashes for data + structures used below. + + It create a unique identifier per module of functions so that different data + structures with slightly different comparison functions won't mix *) diff --git a/test/integration/markdown-with-belt.t/Belt_Id.mli b/test/integration/markdown-with-belt.t/Belt_Id.mli new file mode 100644 index 0000000000..275e9f5a4e --- /dev/null +++ b/test/integration/markdown-with-belt.t/Belt_Id.mli @@ -0,0 +1,10 @@ +(** {!Belt.Id} + + Provide utilities to create identified comparators or hashes for data + structures used below. + + It create a unique identifier per module of functions so that different data + structures with slightly different comparison functions won't mix *) + +type t +(** [t] is the type of the identifier *) diff --git a/test/integration/markdown-with-belt.t/run.t b/test/integration/markdown-with-belt.t/run.t new file mode 100644 index 0000000000..0432b67a0f --- /dev/null +++ b/test/integration/markdown-with-belt.t/run.t @@ -0,0 +1,26 @@ + $ ocamlc -c -bin-annot Belt_Id.mli + $ ocamlc -c -bin-annot Belt.mli + $ odoc compile --package Belt -I . Belt.cmti + $ odoc compile --package Belt -I . Belt_Id.cmti + + $ odoc link Belt.odoc + $ odoc link Belt_Id.odoc + + $ odoc markdown-generate Belt.odocl -o markdown + $ odoc markdown-generate Belt_Id.odocl -o markdown + + $ tree markdown + markdown + `-- Belt + |-- Belt.md + `-- Belt_Id.md + + 1 directory, 2 files + + $ cat markdown/Belt/Belt.md + ``` + module Id = Belt_Id + ``` + [`Belt.Id`](./Belt_Id.md) + Provide utilities to create identified comparators or hashes for data structures used below. + It create a unique identifier per module of functions so that different data structures with slightly different comparison functions won't mix From 5bb46539886572b8e48396ed55bf04d4ea9470cf Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Mon, 28 Apr 2025 16:02:41 +0200 Subject: [PATCH 14/53] Remove toc, sidebar and use_katex from markddown2 --- src/markdown2/generator.ml | 206 ++------------------------------ src/markdown2/generator.mli | 1 - src/markdown2/markdown_page.ml | 5 +- src/markdown2/markdown_page.mli | 6 - src/markdown2/odoc_markdown.ml | 1 - src/markdown2/sidebar.ml | 25 ---- src/markdown2/sidebar.mli | 1 - src/markdown2/types.ml | 21 +--- src/odoc/bin/main.ml | 3 +- 9 files changed, 16 insertions(+), 253 deletions(-) delete mode 100644 src/markdown2/sidebar.ml delete mode 100644 src/markdown2/sidebar.mli diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 812bf1cd13..05067a1f04 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -199,7 +199,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = rows in - (* If we have no data, return an empty paragraph *) if rows_data = [] then [ Md.Block.Paragraph @@ -207,7 +206,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = Md.meta ); ] else - (* Find maximum number of columns across all rows *) let max_columns = List.fold_left (fun max_cols row -> @@ -216,7 +214,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = 0 rows_data in - (* Find out if we have a header row *) let has_header_row = match rows_data with | first_row :: _ -> @@ -226,12 +223,10 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = | [] -> false in - (* Helper to create a list with n elements *) let rec make_list n v = if n <= 0 then [] else v :: make_list (n - 1) v in - (* Create table content with proper Markdown structure *) let header_cells, content_rows = match rows_data with | first_row :: rest when has_header_row -> @@ -253,7 +248,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = if missing > 0 then cells @ make_list missing "" else cells in - (* Create the header row as inline text *) let header_inline = let header_text = "| " ^ String.concat ~sep:" | " header_cells ^ " |" @@ -264,7 +258,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = (* Create the separator row (based on column alignment) *) let separator_inline = - (* Ensure alignment list is the right length *) let alignments = if List.length t.align >= max_columns then (* Take only the first max_columns elements *) @@ -274,7 +267,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = in take max_columns t.align else - (* Pad with defaults *) t.align @ make_list (max_columns - List.length t.align) Table.Default in @@ -296,7 +288,6 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = Md.Inline.Inlines ([ sep_md ], Md.meta) in - (* Create the content rows *) let content_inlines = List.map (fun row -> @@ -306,17 +297,10 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = Md.Inline.Inlines ([ row_md ], Md.meta)) content_rows in - - (* Build all rows in order: header, separator, content *) - let table_inlines = - [ header_inline; separator_inline ] @ content_inlines - in - - (* Create paragraphs for each row *) List.map (fun inline -> Md.Block.Paragraph (Md.Block.Paragraph.make inline, Md.meta)) - table_inlines + ([ header_inline; separator_inline ] @ content_inlines) | Description l -> let item ({ key; definition; attr = _ } : Description.one) = let term = inline ~config ~resolve key in @@ -507,156 +491,6 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = and subpage ~config ~resolve (subp : Subpage.t) = items ~config ~resolve subp.content.items -module Toc = struct - open Odoc_document.Doctree - open Types - - let on_sub : Subpage.status -> bool = function - | `Closed | `Open | `Default -> false - | `Inline -> true - - let gen_toc ~config ~resolve ~path i = - let toc = Toc.compute path ~on_sub i in - let rec section { Toc.url; text; children } = - let _text = inline ~config ~resolve text in - let title = - (* (text) *) - [] - in - let title_str = "" in - let href = Link.href ~config ~resolve url in - { title; title_str; href; children = List.map section children } - in - List.map section toc -end - -module Breadcrumbs = struct - open Types - - let page_parent (page : Url.Path.t) = - let page = - match page with - | { parent = Some parent; name = "index"; kind = `LeafPage } -> parent - | _ -> page - in - match page with - | { parent = None; name = "index"; kind = `LeafPage } -> None - | { parent = Some parent; _ } -> Some parent - | { parent = None; _ } -> - Some { Url.Path.parent = None; name = "index"; kind = `LeafPage } - - let home_breadcrumb ~home_name:_ config ~current_path ~home_path = - let href = - Some - (Link.href ~config ~resolve:(Current current_path) - (Odoc_document.Url.from_path home_path)) - in - { href; name = [ (* Html.txt home_name *) ]; kind = `LeafPage } - - let gen_breadcrumbs_no_sidebar ~config ~url = - let url = - match url with - | { Url.Path.name = "index"; parent = Some parent; kind = `LeafPage } -> - parent - | _ -> url - in - match url with - | { Url.Path.name = "index"; parent = None; kind = `LeafPage } -> - let kind = `LeafPage in - let current = { href = None; name = [ (* Html.txt "" *) ]; kind } in - { parents = []; up_url = None; current } - | url -> ( - (* This is the pre 3.0 way of computing the breadcrumbs *) - let rec get_parent_paths x = - match x with - | [] -> [] - | x :: xs -> ( - match Odoc_document.Url.Path.of_list (List.rev (x :: xs)) with - | Some x -> x :: get_parent_paths xs - | None -> get_parent_paths xs) - in - let to_breadcrumb path = - let href = - Some - (Link.href ~config ~resolve:(Current url) - (Odoc_document.Url.from_path path)) - in - { href; name = [ (* Html.txt path.name *) ]; kind = path.kind } - in - let parent_paths = - get_parent_paths (List.rev (Odoc_document.Url.Path.to_list url)) - |> List.rev - in - match List.rev parent_paths with - | [] -> assert false - | current :: parents -> - let up_url = - match page_parent current with - | None -> None - | Some up -> - Some - (Link.href ~config ~resolve:(Current url) - (Odoc_document.Url.from_path up)) - in - let current = to_breadcrumb current in - let parents = List.map to_breadcrumb parents |> List.rev in - let home = - home_breadcrumb ~home_name:"Index" config ~current_path:url - ~home_path: - { Url.Path.name = "index"; parent = None; kind = `LeafPage } - in - { current; parents = home :: parents; up_url }) - - let gen_breadcrumbs_with_sidebar ~config ~sidebar ~url:current_url = - let find_parent = - List.find_opt (function - | ({ node = { url = { page; anchor = ""; _ }; _ }; _ } : - Odoc_document.Sidebar.entry Tree.t) - when Url.Path.is_prefix page current_url -> - true - | _ -> false) - in - let rec extract acc (tree : Odoc_document.Sidebar.t) = - let parent = - match find_parent tree with - | Some { node = { url; valid_link; content = _; _ }; children } -> - let href = - if valid_link then - Some (Link.href ~config ~resolve:(Current current_url) url) - else None - in - (* let name = inline content in *) - let name = [] in - let breadcrumb = { href; name; kind = url.page.kind } in - if url.page = current_url then Some (`Current breadcrumb) - else Some (`Parent (breadcrumb, children)) - | _ -> None - in - match parent with - | Some (`Parent (bc, children)) -> extract (bc :: acc) children - | Some (`Current current) -> - let up_url = - List.find_map (fun (b : Types.breadcrumb) -> b.href) acc - in - { Types.current; parents = List.rev acc; up_url } - | None -> - let kind = current_url.kind and _name = current_url.name in - let current = { href = None; name = [ (* Html.txt name *) ]; kind } in - let up_url = - List.find_map (fun (b : Types.breadcrumb) -> b.href) acc - in - let parents = List.rev acc in - { Types.current; parents; up_url } - in - let escape = [] in - extract escape sidebar - - let gen_breadcrumbs ~config ~sidebar ~url = - match sidebar with - | None -> gen_breadcrumbs_no_sidebar ~config ~url - | Some sidebar -> gen_breadcrumbs_with_sidebar ~config ~sidebar ~url -end - module Page = struct let on_sub = function | `Page _ -> None @@ -665,55 +499,39 @@ module Page = struct | `Closed | `Open | `Default -> None | `Inline -> Some 0) - let rec include_ ~config ~sidebar { Subpage.content; _ } = - page ~config ~sidebar content + let rec include_ ~config { Subpage.content; _ } = page ~config content - and subpages ~config ~sidebar subpages = - List.map (include_ ~config ~sidebar) subpages + and subpages ~config subpages = List.map (include_ ~config) subpages - and page ~config ~sidebar p : Odoc_document.Renderer.page = + and page ~config p : Odoc_document.Renderer.page = let { Page.preamble = _; items = i; url; source_anchor } = Doctree.Labels.disambiguate_page ~enter_subpages:false p in - let subpages = subpages ~config ~sidebar @@ Doctree.Subpages.compute p in + let subpages = subpages ~config @@ Doctree.Subpages.compute p in let resolve = Link.Current url in - let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~sidebar ~url in - let sidebar = - (* match sidebar with - | None -> None - | Some sidebar -> - let sidebar = Odoc_document.Sidebar.to_block sidebar url in - (Some (block ~config ~resolve sidebar) :> any Html.elt list option) *) - None - in let i = Doctree.Shift.compute ~on_sub i in - let uses_katex = Doctree.Math.has_math_elements p in - let toc = Toc.gen_toc ~config ~resolve ~path:url i in let content = items ~config ~resolve i in let root_block = Md.Block.Blocks (content, Md.meta) in let doc = Cmarkit.Doc.make root_block in let header, preamble = Doctree.PageTitle.render_title ?source_anchor p in let header = items ~config ~resolve header in let preamble = items ~config ~resolve preamble in - Markdown_page.make ~sidebar ~config ~header:(header @ preamble) ~toc - ~breadcrumbs ~url ~uses_katex doc subpages + Markdown_page.make ~config ~header:(header @ preamble) ~url doc subpages - and source_page ~config ~sidebar sp = - (* TODO: I'm not enturely sure when this is called *) + and source_page ~config sp = let { Source_page.url; contents = _ } = sp in let _resolve = Link.Current sp.url in - let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~sidebar ~url in - let sidebar = None in let title = url.Url.Path.name and doc = [ Md.Block.empty ] in + (* What's the header? *) let header = [] in - Markdown_page.make_src ~breadcrumbs ~header ~config ~url ~sidebar title doc + Markdown_page.make_src ~header ~config ~url title doc end -let render ~(config : Config.t) ~sidebar = function +let render ~(config : Config.t) = function (* .mld *) - | Document.Page page -> [ Page.page ~config ~sidebar page ] + | Document.Page page -> [ Page.page ~config page ] (* .mli docs *) - | Source_page src -> [ Page.source_page ~config ~sidebar src ] + | Source_page src -> [ Page.source_page ~config src ] let filepath ~config url = Link.Path.as_filename ~config url diff --git a/src/markdown2/generator.mli b/src/markdown2/generator.mli index 5415581fec..8ace3211b1 100644 --- a/src/markdown2/generator.mli +++ b/src/markdown2/generator.mli @@ -1,6 +1,5 @@ val render : config:Config.t -> - sidebar:Odoc_document.Sidebar.t option -> Odoc_document.Types.Document.t -> Odoc_document.Renderer.page list diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index e4c620e0f6..10c307b2d7 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -21,8 +21,7 @@ let page_creator doc = let renderer = Cmarkit_commonmark.renderer () in Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) -let make ~config ~url ~header:_ ~breadcrumbs:_ ~sidebar:_ ~toc:_ ~uses_katex:_ - content children = +let make ~config ~url ~header:_ content children = let filename = Link.Path.as_filename ~config url in let content = page_creator content in { Odoc_document.Renderer.filename; content; children; path = url } @@ -34,7 +33,7 @@ let src_page_creator _name (block_list : Cmarkit.Block.t list) = let doc = Cmarkit.Doc.make root_block in Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) -let make_src ~config ~url ~breadcrumbs:_ ~header:_ ~sidebar:_ title content = +let make_src ~config ~url ~header:_ title content = let filename = Link.Path.as_filename ~config url in let content = src_page_creator title content in { Odoc_document.Renderer.filename; content; children = []; path = url } diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index 814f106243..cb6a0c3f9a 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -22,10 +22,6 @@ val make : config:Config.t -> url:Odoc_document.Url.Path.t -> header:Cmarkit.Block.t list -> - breadcrumbs:Types.breadcrumbs -> - sidebar:Cmarkit.Block.t list option -> - toc:Types.toc list -> - uses_katex:bool -> Cmarkit.Doc.t -> Odoc_document.Renderer.page list -> Odoc_document.Renderer.page @@ -33,9 +29,7 @@ val make : val make_src : config:Config.t -> url:Odoc_document.Url.Path.t -> - breadcrumbs:Types.breadcrumbs -> header:Cmarkit.Block.t list -> - sidebar:Cmarkit.Block.t list option -> string -> Cmarkit.Block.t list -> Odoc_document.Renderer.page diff --git a/src/markdown2/odoc_markdown.ml b/src/markdown2/odoc_markdown.ml index 63facdde9e..07c829270c 100644 --- a/src/markdown2/odoc_markdown.ml +++ b/src/markdown2/odoc_markdown.ml @@ -7,4 +7,3 @@ module Markdown_page = Markdown_page module Generator = Generator module Link = Link module Json = Odoc_utils.Json -module Sidebar = Sidebar diff --git a/src/markdown2/sidebar.ml b/src/markdown2/sidebar.ml deleted file mode 100644 index 59996fee2f..0000000000 --- a/src/markdown2/sidebar.ml +++ /dev/null @@ -1,25 +0,0 @@ -open Odoc_utils - -let toc_to_json - ({ url; valid_link; content = _; _ } : Odoc_document.Sidebar.entry) : - Json.json = - (* let config = - Config.v ~semantic_uris:true ~indent:true ~flat:false ~open_details:false - ~as_json:true ~remap:[] () - in *) - let url, kind = - match valid_link with - | false -> (`Null, `Null) - | true -> - let _href = Link.href ~resolve:(Link.Base "") url in - let kind = - Format.asprintf "%a" Odoc_document.Url.Anchor.pp_kind url.kind - in - - (`String "TODO", `String kind) - in - let inline = `String "TODO" in - `Object [ ("url", url); ("kind", kind); ("content", inline) ] - -let to_json (sidebar : Odoc_document.Sidebar.t) = - `Array (List.map (Tree.to_json toc_to_json) sidebar) diff --git a/src/markdown2/sidebar.mli b/src/markdown2/sidebar.mli deleted file mode 100644 index 77458ad0f3..0000000000 --- a/src/markdown2/sidebar.mli +++ /dev/null @@ -1 +0,0 @@ -val to_json : Odoc_document.Sidebar.t -> Odoc_utils.Json.json diff --git a/src/markdown2/types.ml b/src/markdown2/types.ml index 73699470f6..b3653f3f14 100644 --- a/src/markdown2/types.ml +++ b/src/markdown2/types.ml @@ -1,24 +1,5 @@ -(* Type definitions for the HTML renderer *) +(* Type definitions for the Markdown renderer *) type uri = Absolute of string | Relative of Odoc_document.Url.Path.t option type file_uri = Absolute of string | Relative of Odoc_document.Url.Path.t - -type toc = { - title : Html_types.flow5_without_interactive Tyxml.Html.elt list; - title_str : string; - href : string; - children : toc list; -} - -type breadcrumb = { - href : string option; - name : Html_types.phrasing_without_interactive Tyxml.Html.elt list; - kind : Odoc_document.Url.Path.kind; -} - -type breadcrumbs = { - parents : breadcrumb list; - current : breadcrumb; - up_url : string option; -} diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 9d49aee177..815519ee9b 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1315,8 +1315,7 @@ module Odoc_html = Make_renderer (Odoc_html_args) module Odoc_markdown_cmd = Make_renderer (struct type args = Odoc_markdown.Config.t - let render config sidebar page = - Odoc_markdown.Generator.render ~config ~sidebar page + let render config _sidebar page = Odoc_markdown.Generator.render ~config page let filepath _url = failwith "Not implemented" (* Odoc_html.Generator.filepath ~config:html_config url *) From eba77533d276c5c2688de63d5cdb7d05dda41d38 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 30 Apr 2025 12:48:56 +0100 Subject: [PATCH 15/53] Abstract block_table and remove opens --- src/markdown2/config.ml | 2 - src/markdown2/generator.ml | 345 ++++++++++++-------------- src/markdown2/generator.mli | 2 +- src/markdown2/link.ml | 1 + src/markdown2/markdown_page.ml | 28 +-- src/markdown2/markdown_source.ml | 81 ------ src/markdown2/markdown_source.mli | 5 - src/markdown2/odoc_markdown.ml | 5 - src/markdown2/types.ml | 5 - test/integration/markdown.t/array.mli | 6 +- test/integration/markdown.t/page.mld | 6 +- test/integration/markdown.t/run.t | 86 ++++++- 12 files changed, 255 insertions(+), 317 deletions(-) delete mode 100644 src/markdown2/markdown_source.ml delete mode 100644 src/markdown2/markdown_source.mli delete mode 100644 src/markdown2/types.ml diff --git a/src/markdown2/config.ml b/src/markdown2/config.ml index c85427449b..cb104e601c 100644 --- a/src/markdown2/config.ml +++ b/src/markdown2/config.ml @@ -1,7 +1,5 @@ (* Markdown output configuration *) -[@@@warning "-69"] - type t = { root_url : string option } let v ~root_url () = { root_url } diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 05067a1f04..7ef04b2432 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -1,37 +1,18 @@ -(* - * Copyright (c) 2016 Thomas Refis - * - * Permission to use, copy, modify, and distribute this software for any - * purpose with or without fee is hereby granted, provided that the above - * copyright notice and this permission notice appear in all copies. - * - * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - *) - -[@@@warning "-26-27-32"] - open Odoc_utils - module HLink = Link -open Odoc_document.Types + +module Types = Odoc_document.Types module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url module Link = HLink module Md = struct include Cmarkit - let meta = Cmarkit.Meta.none end -let source fn (t : Source.t) = - let rec token (x : Source.token) = +let source fn (t : Types.Source.t) = + let rec token (x : Types.Source.token) = match x with Elt i -> fn i | Tag (_, l) -> tokens l and tokens t = List.concat_map token t in tokens t @@ -56,7 +37,7 @@ let entity = function "#45" -> "-" | "gt" -> ">" | e -> "&" ^ e ^ ";" let rec inline_text_only inline = List.concat_map - (fun (i : Inline.one) -> + (fun (i : Types.Inline.one) -> match i.desc with | Text "" -> [] | Text s -> [ s ] @@ -68,9 +49,9 @@ let rec inline_text_only inline = | _ -> []) inline -and block_text_only (blocks : Block.t) : string list = +and block_text_only blocks : string list = List.concat_map - (fun (b : Block.one) -> + (fun (b : Types.Block.one) -> match b.desc with | Paragraph inline | Inline inline -> inline_text_only inline | Source (_, s) -> source inline_text_only s @@ -79,8 +60,8 @@ and block_text_only (blocks : Block.t) : string list = | _ -> []) blocks -and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = - let one (t : Inline.one) = +and inline ~config ?(emph_level = 0) ~resolve l = + let one (t : Types.Inline.one) = match t.desc with | Text s -> [ Md.Inline.Text (s, Md.meta) ] | Entity s -> @@ -141,17 +122,8 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) = in List.concat_map one l -let heading ~config ~resolve (h : Heading.t) : Md.Block.t list = - let inlines = inline ~config ~resolve h.title in - let content = Md.Inline.Inlines (inlines, Md.meta) in - let heading = - Md.Block.Heading - (Md.Block.Heading.make ~level:(h.level + 1) content, Md.meta) - in - [ heading ] - -let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = - let one (t : Block.one) : Md.Block.t list = +let rec block ~config ~resolve l = + let one (t : Types.Block.one) = match t.desc with | Paragraph paragraph -> let inlines = inline ~config ~resolve paragraph in @@ -175,134 +147,16 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = l in [ - (* TODO: Do we need to make it tight based on something? *) + (* TODO: Do we need the list (~tight:false) based on surrounding content or can we always be ~tight:true? *) Md.Block.List (Md.Block.List'.make ~tight:true list_type list_items, Md.meta); ] | Inline i -> let inlines = Md.Inline.Inlines (inline ~config ~resolve i, Md.meta) in [ Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) ] - | Table t -> - let rows_data : (string * [ `Data | `Header ]) list list = - match t.data with - | [] -> [] - | rows -> - List.map - (fun (row : (Block.t * [ `Data | `Header ]) list) -> - List.map - (fun (content, cell_type) -> - let cell_text = - String.concat ~sep:" " (block_text_only content) - in - (cell_text, cell_type)) - row) - rows - in - - if rows_data = [] then - [ - Md.Block.Paragraph - ( Md.Block.Paragraph.make (Md.Inline.Inlines ([], Md.meta)), - Md.meta ); - ] - else - let max_columns = - List.fold_left - (fun max_cols row -> - let row_cols = List.length row in - if row_cols > max_cols then row_cols else max_cols) - 0 rows_data - in - - let has_header_row = - match rows_data with - | first_row :: _ -> - List.exists - (fun (_, cell_type) -> cell_type = `Header) - first_row - | [] -> false - in - - let rec make_list n v = - if n <= 0 then [] else v :: make_list (n - 1) v - in - - let header_cells, content_rows = - match rows_data with - | first_row :: rest when has_header_row -> - (* Pad header cells to match max_columns *) - let padded_header = - let cells = List.map fst first_row in - let missing = max_columns - List.length cells in - if missing > 0 then cells @ make_list missing "" else cells - in - (padded_header, rest) - | _ -> - (* No header - create an empty header matching the max columns *) - (make_list max_columns "", rows_data) - in - - let pad_row row = - let cells = List.map fst row in - let missing = max_columns - List.length cells in - if missing > 0 then cells @ make_list missing "" else cells - in - - let header_inline = - let header_text = - "| " ^ String.concat ~sep:" | " header_cells ^ " |" - in - let header_md = Md.Inline.Text (header_text, Md.meta) in - Md.Inline.Inlines ([ header_md ], Md.meta) - in - - (* Create the separator row (based on column alignment) *) - let separator_inline = - let alignments = - if List.length t.align >= max_columns then - (* Take only the first max_columns elements *) - let rec take n lst = - if n <= 0 then [] - else match lst with [] -> [] | h :: t -> h :: take (n - 1) t - in - take max_columns t.align - else - t.align - @ make_list (max_columns - List.length t.align) Table.Default - in - - let separator_cells = - List.map - (fun align -> - match align with - | Table.Left -> ":---" - | Table.Center -> ":---:" - | Table.Right -> "---:" - | Table.Default -> "---") - alignments - in - let sep_text = - "| " ^ String.concat ~sep:" | " separator_cells ^ " |" - in - let sep_md = Md.Inline.Text (sep_text, Md.meta) in - Md.Inline.Inlines ([ sep_md ], Md.meta) - in - - let content_inlines = - List.map - (fun row -> - let cells = pad_row row in - let row_text = "| " ^ String.concat ~sep:" | " cells ^ " |" in - let row_md = Md.Inline.Text (row_text, Md.meta) in - Md.Inline.Inlines ([ row_md ], Md.meta)) - content_rows - in - List.map - (fun inline -> - Md.Block.Paragraph (Md.Block.Paragraph.make inline, Md.meta)) - ([ header_inline; separator_inline ] @ content_inlines) + | Table t -> block_table t | Description l -> - let item ({ key; definition; attr = _ } : Description.one) = + let item ({ key; definition; attr = _ } : Types.Description.one) = let term = inline ~config ~resolve key in (* We extract definition as inline, since it came as "Block". There seems to be no way (in Cmarkit) to make it inline *) let definition_inline = @@ -352,19 +206,19 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = in failwith msg) | Audio (_target, _alt) -> - (* TODO: Raise a decent error here? Only saw assert false :( *) + (* TODO: Raise a decent error here? Maybe warnings, I only saw assert false *) failwith "Audio isn't supported in markdown" | Video (_target, _alt) -> - (* TODO: Raise a decent error here? Only saw assert false :( *) + (* TODO: Raise a decent error here? Maybe warnings, I only saw assert false *) failwith "Video isn't supported in markdown" | Image (target, alt) -> let dest = - match target with - | Target.External url -> (url, Md.meta) - | Target.Internal (Resolved uri) -> + match (target : Types.Target.t) with + | External url -> (url, Md.meta) + | Internal (Resolved uri) -> let url = Link.href ~config ~resolve uri in (url, Md.meta) - | Target.Internal Unresolved -> + | Internal Unresolved -> (* TODO: What's unresolved? A non-existing page/link? *) ("", Md.meta) in @@ -383,8 +237,119 @@ let rec block ~config ~resolve (l : Block.t) : Md.Block.t list = in List.concat_map one l +and block_table t = + let rows_data : (string * [ `Data | `Header ]) list list = + match t.data with + | [] -> [] + | rows -> + List.map + (fun (row : (Types.Block.t * [ `Data | `Header ]) list) -> + List.map + (fun (content, cell_type) -> + let cell_text = + String.concat ~sep:" " (block_text_only content) + in + (cell_text, cell_type)) + row) + rows + in + + if rows_data = [] then + [ + Md.Block.Paragraph + (Md.Block.Paragraph.make (Md.Inline.Inlines ([], Md.meta)), Md.meta); + ] + else + let max_columns = + List.fold_left + (fun max_cols row -> + let row_cols = List.length row in + if row_cols > max_cols then row_cols else max_cols) + 0 rows_data + in + + let has_header_row = + match rows_data with + | first_row :: _ -> + List.exists (fun (_, cell_type) -> cell_type = `Header) first_row + | [] -> false + in + + let rec make_list n v = if n <= 0 then [] else v :: make_list (n - 1) v in + + let header_cells, content_rows = + match rows_data with + | first_row :: rest when has_header_row -> + (* Pad header cells to match max_columns *) + let padded_header = + let cells = List.map fst first_row in + let missing = max_columns - List.length cells in + if missing > 0 then cells @ make_list missing "" else cells + in + (padded_header, rest) + | _ -> + (* No header - create an empty header matching the max columns *) + (make_list max_columns "", rows_data) + in + + let pad_row row = + let cells = List.map fst row in + let missing = max_columns - List.length cells in + if missing > 0 then cells @ make_list missing "" else cells + in + + let header_inline = + let header_text = "| " ^ String.concat ~sep:" | " header_cells ^ " |" in + let header_md = Md.Inline.Text (header_text, Md.meta) in + Md.Inline.Inlines ([ header_md ], Md.meta) + in + + (* Create the separator row (based on column alignment) *) + let separator_inline = + let alignments = + if List.length t.align >= max_columns then + (* Take only the first max_columns elements *) + let rec take n lst = + if n <= 0 then [] + else match lst with [] -> [] | h :: t -> h :: take (n - 1) t + in + take max_columns t.align + else + t.align + @ make_list (max_columns - List.length t.align) Types.Table.Default + in + + let separator_cells = + List.map + (fun align -> + match (align : Types.Table.alignment) with + | Left -> ":---" + | Center -> ":---:" + | Right -> "---:" + | Default -> "---") + alignments + in + let sep_text = "| " ^ String.concat ~sep:" | " separator_cells ^ " |" in + let sep_md = Md.Inline.Text (sep_text, Md.meta) in + Md.Inline.Inlines ([ sep_md ], Md.meta) + in + + let content_inlines = + List.map + (fun row -> + let cells = pad_row row in + let row_text = "| " ^ String.concat ~sep:" | " cells ^ " |" in + let row_md = Md.Inline.Text (row_text, Md.meta) in + Md.Inline.Inlines ([ row_md ], Md.meta)) + content_rows + in + List.map + (fun inline -> + Md.Block.Paragraph (Md.Block.Paragraph.make inline, Md.meta)) + ([ header_inline; separator_inline ] @ content_inlines) + and items ~config ~resolve l : Md.Block.t list = - let rec walk_items acc (t : Item.t list) = + let rec walk_items acc (t : Types.Item.t list) = let continue_with rest elts = (walk_items [@tailcall]) (List.rev_append elts acc) rest in @@ -393,13 +358,17 @@ and items ~config ~resolve l : Md.Block.t list = | Text _ :: _ as t -> let text, _, rest = Doctree.Take.until t ~classify:(function - | Item.Text text -> Accum text + | Types.Item.Text text -> Accum text | _ -> Stop_and_keep) in let content = block ~config ~resolve text in (continue_with [@tailcall]) rest content | Heading h :: rest -> - (continue_with [@tailcall]) rest (heading ~config ~resolve h) + let inlines = inline ~config ~resolve h.title in + let content = Md.Inline.Inlines (inlines, Md.meta) in + let block = Md.Block.Heading.make ~level:(h.level + 1) content in + let heading = [ Md.Block.Heading (block, Md.meta) ] in + (continue_with [@tailcall]) rest heading | Include { attr = _attr; @@ -413,7 +382,7 @@ and items ~config ~resolve l : Md.Block.t list = (continue_with [@tailcall]) rest content | Declaration { - Item.attr = _attr; + attr = _attr; anchor = _anchor; source_anchor = _source_anchor; content; @@ -427,11 +396,11 @@ and items ~config ~resolve l : Md.Block.t list = and items l = walk_items [] l in items l -and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = - let open DocumentedSrc in +and documentedSrc ~config ~resolve t = + let open Types.DocumentedSrc in let take_code l = Doctree.Take.until l ~classify:(fun x -> - match (x : DocumentedSrc.one) with + match (x : one) with | Code code -> Accum code | Alternative (Expansion { summary; _ }) -> Accum summary | _ -> Stop_and_keep) @@ -439,11 +408,9 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = let take_descr l = Doctree.Take.until l ~classify:(function | Documented { attrs; anchor; code; doc; markers } -> - Accum - [ { DocumentedSrc.attrs; anchor; code = `D code; doc; markers } ] + Accum [ { attrs; anchor; code = `D code; doc; markers } ] | Nested { attrs; anchor; code; doc; markers } -> - Accum - [ { DocumentedSrc.attrs; anchor; code = `N code; doc; markers } ] + Accum [ { attrs; anchor; code = `N code; doc; markers } ] | _ -> Stop_and_keep) in let rec to_markdown t : Md.Block.t list = @@ -466,8 +433,7 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = | Subpage subp :: _ -> subpage ~config ~resolve subp | (Documented _ | Nested _) :: _ -> let l, _, rest = take_descr t in - let one { DocumentedSrc.attrs = _; anchor = _; code; doc; markers = _ } - = + let one { attrs = _; anchor = _; code; doc; markers = _ } = let content = match code with | `D code -> @@ -488,23 +454,23 @@ and documentedSrc ~config ~resolve (t : DocumentedSrc.t) = in to_markdown t -and subpage ~config ~resolve (subp : Subpage.t) = +and subpage ~config ~resolve (subp : Types.Subpage.t) = items ~config ~resolve subp.content.items module Page = struct let on_sub = function | `Page _ -> None - | `Include x -> ( - match x.Include.status with + | `Include (x : Types.Include.t) -> ( + match x.status with | `Closed | `Open | `Default -> None | `Inline -> Some 0) - let rec include_ ~config { Subpage.content; _ } = page ~config content + let rec include_ ~config { Types.Subpage.content; _ } = page ~config content and subpages ~config subpages = List.map (include_ ~config) subpages and page ~config p : Odoc_document.Renderer.page = - let { Page.preamble = _; items = i; url; source_anchor } = + let { Types.Page.preamble = _; items = i; url; source_anchor } = Doctree.Labels.disambiguate_page ~enter_subpages:false p in let subpages = subpages ~config @@ Doctree.Subpages.compute p in @@ -512,14 +478,14 @@ module Page = struct let i = Doctree.Shift.compute ~on_sub i in let content = items ~config ~resolve i in let root_block = Md.Block.Blocks (content, Md.meta) in - let doc = Cmarkit.Doc.make root_block in + let doc = Md.Doc.make root_block in let header, preamble = Doctree.PageTitle.render_title ?source_anchor p in let header = items ~config ~resolve header in let preamble = items ~config ~resolve preamble in Markdown_page.make ~config ~header:(header @ preamble) ~url doc subpages and source_page ~config sp = - let { Source_page.url; contents = _ } = sp in + let { Types.Source_page.url; contents = _ } = sp in let _resolve = Link.Current sp.url in let title = url.Url.Path.name and doc = [ Md.Block.empty ] in (* What's the header? *) @@ -527,14 +493,13 @@ module Page = struct Markdown_page.make_src ~header ~config ~url title doc end -let render ~(config : Config.t) = function +let render ~(config : Config.t) doc = + match (doc : Types.Document.t) with (* .mld *) - | Document.Page page -> [ Page.page ~config page ] + | Page page -> [ Page.page ~config page ] (* .mli docs *) | Source_page src -> [ Page.source_page ~config src ] -let filepath ~config url = Link.Path.as_filename ~config url - let inline ~config ~xref_base_uri b = let resolve = Link.Base xref_base_uri in inline ~config ~resolve b diff --git a/src/markdown2/generator.mli b/src/markdown2/generator.mli index 8ace3211b1..7cc6ca53dc 100644 --- a/src/markdown2/generator.mli +++ b/src/markdown2/generator.mli @@ -3,7 +3,7 @@ val render : Odoc_document.Types.Document.t -> Odoc_document.Renderer.page list -val filepath : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t +(* val filepath : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t *) val items : config:Config.t -> diff --git a/src/markdown2/link.ml b/src/markdown2/link.ml index 85939ac359..2c4d700289 100644 --- a/src/markdown2/link.ml +++ b/src/markdown2/link.ml @@ -111,4 +111,5 @@ let href ~config ~resolve t = in match (relative_target, anchor) with | [], "" -> "#" + (* TODO: This looks wrong ./ could technically be the current page *) | page, _ -> "./" ^ add_anchor @@ String.concat "/" page)) diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index 10c307b2d7..998e662875 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -16,24 +16,20 @@ module Url = Odoc_document.Url -let page_creator doc = - fun (ppf : Format.formatter) -> - let renderer = Cmarkit_commonmark.renderer () in - Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) - -let make ~config ~url ~header:_ content children = +let make ~config ~url ~header:_ doc children = let filename = Link.Path.as_filename ~config url in - let content = page_creator content in + let content ppf = + let renderer = Cmarkit_commonmark.renderer () in + Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) + in { Odoc_document.Renderer.filename; content; children; path = url } -let src_page_creator _name (block_list : Cmarkit.Block.t list) = - fun (ppf : Format.formatter) -> - let renderer = Cmarkit_commonmark.renderer () in - let root_block = Cmarkit.Block.Blocks (block_list, Cmarkit.Meta.none) in - let doc = Cmarkit.Doc.make root_block in - Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) - -let make_src ~config ~url ~header:_ title content = +let make_src ~config ~url ~header:_ _title block_list = let filename = Link.Path.as_filename ~config url in - let content = src_page_creator title content in + let content (ppf : Format.formatter) = + let renderer = Cmarkit_commonmark.renderer () in + let root_block = Cmarkit.Block.Blocks (block_list, Cmarkit.Meta.none) in + let doc = Cmarkit.Doc.make root_block in + Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) + in { Odoc_document.Renderer.filename; content; children = []; path = url } diff --git a/src/markdown2/markdown_source.ml b/src/markdown2/markdown_source.ml deleted file mode 100644 index de5257e57e..0000000000 --- a/src/markdown2/markdown_source.ml +++ /dev/null @@ -1,81 +0,0 @@ -open Odoc_utils -module HLink = Link -open Odoc_document.Types -open Tyxml -module Link = HLink - -let html_of_doc ~config ~resolve docs = - let open Html in - let a : - ( [< Html_types.a_attrib ], - [< Html_types.span_content_fun ], - [> Html_types.span ] ) - star = - Unsafe.node "a" - (* Makes it possible to use inside span. Although this is not standard (see - https://developer.mozilla.org/en-US/docs/Web/Guide/HTML/Content_categories) - it is validated by the {{:https://validator.w3.org/nu/#textarea}W3C}. *) - in - (* [a] tags should not contain in other [a] tags. If this happens, browsers - start to be really weird. If PPX do bad things, such a situation could - happen. We manually avoid this situation. *) - let rec doc_to_html ~is_in_a doc = - match doc with - | Source_page.Plain_code s -> [ txt s ] - | Tagged_code (info, docs) -> ( - let is_in_a = match info with Link _ -> true | _ -> is_in_a in - let children = List.concat_map (doc_to_html ~is_in_a) docs in - match info with - | Syntax tok -> [ span ~a:[ a_class [ tok ] ] children ] - (* Currently, we do not render links to documentation *) - | Link { documentation = _; implementation = None } -> children - | Link { documentation = _; implementation = Some anchor } -> - let href = Link.href ~config ~resolve anchor in - [ a ~a:[ a_href href ] children ] - | Anchor lbl -> [ span ~a:[ a_id lbl ] children ]) - in - let span_content = List.concat_map (doc_to_html ~is_in_a:false) docs in - span ~a:[] span_content - -let count_lines_in_string s = - let n = ref 0 in - String.iter (function '\n' -> incr n | _ -> ()) s; - !n - -(** Traverse the doc to count the number of lines. *) -let rec count_lines_in_span = function - | Source_page.Plain_code s -> count_lines_in_string s - | Tagged_code (_, docs) -> count_lines docs - -and count_lines l = - let rec inner l acc = - match l with - | [] -> acc - | hd :: tl -> inner tl (count_lines_in_span hd + acc) - in - inner l 0 - -let rec line_numbers acc n = - let open Html in - if n < 1 then acc - else - let l = string_of_int n in - let anchor = - a - ~a:[ a_id ("L" ^ l); a_class [ "source_line" ]; a_href ("#L" ^ l) ] - [ txt l ] - in - line_numbers (anchor :: txt "\n" :: acc) (n - 1) - -let html_of_doc ~config ~resolve docs = - let open Html in - pre - ~a:[ a_class [ "source_container" ] ] - [ - code - ~a:[ a_class [ "source_line_column" ] ] - (line_numbers [] (count_lines docs)); - code - ~a:[ a_class [ "source_code" ] ] - [ html_of_doc ~config ~resolve docs ]; - ] diff --git a/src/markdown2/markdown_source.mli b/src/markdown2/markdown_source.mli deleted file mode 100644 index 1e09f4bd61..0000000000 --- a/src/markdown2/markdown_source.mli +++ /dev/null @@ -1,5 +0,0 @@ -val html_of_doc : - config:Config.t -> - resolve:Link.resolve -> - Odoc_document.Types.Source_page.code -> - [> Html_types.pre ] Tyxml.Html.elt diff --git a/src/markdown2/odoc_markdown.ml b/src/markdown2/odoc_markdown.ml index 07c829270c..ff2edbd09c 100644 --- a/src/markdown2/odoc_markdown.ml +++ b/src/markdown2/odoc_markdown.ml @@ -1,9 +1,4 @@ -module Types = Types module Config = Config - module Markdown_page = Markdown_page -(** @canonical Odoc_html.Html_page *) - module Generator = Generator module Link = Link -module Json = Odoc_utils.Json diff --git a/src/markdown2/types.ml b/src/markdown2/types.ml deleted file mode 100644 index b3653f3f14..0000000000 --- a/src/markdown2/types.ml +++ /dev/null @@ -1,5 +0,0 @@ -(* Type definitions for the Markdown renderer *) - -type uri = Absolute of string | Relative of Odoc_document.Url.Path.t option - -type file_uri = Absolute of string | Relative of Odoc_document.Url.Path.t diff --git a/test/integration/markdown.t/array.mli b/test/integration/markdown.t/array.mli index 8613eda85f..9cd2006544 100644 --- a/test/integration/markdown.t/array.mli +++ b/test/integration/markdown.t/array.mli @@ -1,6 +1,6 @@ -(** {0 List} +(** {0 Array} - Utilities for List data type. + Utilities for Array data type. This module is compatible with original ocaml stdlib. In general, all functions comes with the original stdlib also applies to this collection, @@ -25,7 +25,7 @@ val size : 'a t -> int val head : 'a t -> 'a option (** [head xs] returns [None] if [xs] is the empty list, otherwise it returns - [Some value] where [value] is the first element in the list. + [Some value] where [val ue] is the first element in the list. {[ head [] = None;; head [ 1; 2; 3 ] = Some 1 diff --git a/test/integration/markdown.t/page.mld b/test/integration/markdown.t/page.mld index f7c221202f..1370b972ac 100644 --- a/test/integration/markdown.t/page.mld +++ b/test/integration/markdown.t/page.mld @@ -22,11 +22,9 @@ You can also click {{:https://www.example.com}here}. {3 References} -See [Odoc_odoc.Compile.compile]. +See an empty reference {{!test.v}}. -See [Odoc_odoc.Compile.compile]. - -See {{!/test.v}this function from another library}. +See {{!test.v}this function from another library}. See {{!./test.mli}this page from another package}. diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 84a5053873..305624aad5 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -2,7 +2,9 @@ $ ocamlc -c -bin-annot test2.mli $ ocamlc -c -bin-annot list.mli $ odoc compile --package test -I . page.mld - File "page.mld", line 123, characters 0-11: + File "page.mld", line 25, characters 23-34: + Warning: '{{!...} ...}' (cross-reference) should not be empty. + File "page.mld", line 121, characters 0-11: Warning: Tags are not allowed in pages. $ odoc compile --package test test.cmti $ odoc compile --package test -I . test2.cmti @@ -15,12 +17,10 @@ File "list.mli", line 37, characters 12-19: Warning: Reference to 'head' is ambiguous. Please specify its kind: section-head, val-head. $ odoc link page-page.odoc - File "page.mld", line 83, characters 0-33: + File "page.mld", line 81, characters 0-33: Warning: Failed to resolve reference ./odoc_logo_placeholder.jpg Path 'odoc_logo_placeholder.jpg' not found - File "page.mld", line 31, characters 4-49: + File "page.mld", line 29, characters 4-49: Warning: Failed to resolve reference ./test.mli Path 'test' not found - File "page.mld", line 29, characters 4-50: - Warning: Failed to resolve reference /test.v Path '/test' not found $ odoc markdown-generate test.odocl -o markdown $ odoc markdown-generate test2.odocl -o markdown $ odoc markdown-generate page-page.odocl -o markdown @@ -40,3 +40,79 @@ ``` module List : sig ... end ``` + + $ cat markdown/test/page.md + ## Title + ### Subtitle + #### Referenceable title + See [Referenceable title](./#my_id). + #### Styled + **bold** text, *italic* text, *emphasized* text + H2O and 1st + #### Link + Here is a link: [https://www.example.com](https://www.example.com). + You can also click [here](https://www.example.com). + #### References + See an empty reference [`Test.v`](./Test.md#val-v). + See [this function from another library](./Test.md#val-v). + See [this page from another package](). + See [this section](./#styled) for the syntax of references. + #### Lists + - First item + - Second item + 0. First ordered item + 1. Second numbered item + - First item + - Second item + - can also be used + 0. First numbered item + 1. Second numbered item + 2. can also be used + #### Code blocks + Inline `code`. + ```ocaml + let _ = "Block code" + ``` + ```text + Code block with {[inner code block syntax]} + ``` + ```python + [i+1 for i in xrange(2)] + ``` + #### Verbatim + ``` + verbatim text + ``` + #### Math + For inline math: `\sqrt 2`. + For display math: + ``` + \sqrt 2 + ``` + #### Images + ![./odoc\_logo\_placeholder.jpg]() + ![https://picsum.photos/200/100](https://picsum.photos/200/100) + #### Table + ##### Explicit syntax + \| Header 1 \| Header 2 \| + \| --- \| --- \| + \| Cell 1 \| Cell 2 \| + \| Cell 3 \| Cell 4 \| + ##### Light syntax + \| Header 1 \| Header 2 \| + \| --- \| --- \| + \| Cell 1 \| Cell 2 \| + \| Cell 3 \| Cell 4 \| + #### HTML + This is a strong tag: Odoc language lack support for quotation! + + +
+
+ Odoc language lack support for quotation! +
+
+ + #### Tags + since 4\.08 + Tags are explained in this section. From 719b4eb8d14305c784dda28b9e4684bce22f2fa5 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 30 Apr 2025 12:59:24 +0100 Subject: [PATCH 16/53] Render header and preamble in page --- src/markdown2/generator.ml | 18 ++++++++++-------- src/markdown2/markdown_page.ml | 8 +++++--- src/markdown2/markdown_page.mli | 1 - test/integration/markdown.t/run.t | 15 +++++++++++++++ 4 files changed, 30 insertions(+), 12 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 7ef04b2432..ff0ad0ef96 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -476,20 +476,22 @@ module Page = struct let subpages = subpages ~config @@ Doctree.Subpages.compute p in let resolve = Link.Current url in let i = Doctree.Shift.compute ~on_sub i in - let content = items ~config ~resolve i in - let root_block = Md.Block.Blocks (content, Md.meta) in - let doc = Md.Doc.make root_block in let header, preamble = Doctree.PageTitle.render_title ?source_anchor p in let header = items ~config ~resolve header in let preamble = items ~config ~resolve preamble in - Markdown_page.make ~config ~header:(header @ preamble) ~url doc subpages + let content = items ~config ~resolve i in + let root_block = Md.Block.Blocks (header @ preamble @ content, Md.meta) in + let doc = Md.Doc.make root_block in + Markdown_page.make ~config ~url doc subpages and source_page ~config sp = let { Types.Source_page.url; contents = _ } = sp in - let _resolve = Link.Current sp.url in - let title = url.Url.Path.name and doc = [ Md.Block.empty ] in - (* What's the header? *) - let header = [] in + let resolve = Link.Current sp.url in + let title = url.Url.Path.name in + let doc = [ Md.Block.empty ] in + let header = + items ~config ~resolve (Doctree.PageTitle.render_src_title sp) + in Markdown_page.make_src ~header ~config ~url title doc end diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index 998e662875..9d0de18eaa 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -16,7 +16,7 @@ module Url = Odoc_document.Url -let make ~config ~url ~header:_ doc children = +let make ~config ~url doc children = let filename = Link.Path.as_filename ~config url in let content ppf = let renderer = Cmarkit_commonmark.renderer () in @@ -24,11 +24,13 @@ let make ~config ~url ~header:_ doc children = in { Odoc_document.Renderer.filename; content; children; path = url } -let make_src ~config ~url ~header:_ _title block_list = +let make_src ~config ~url ~header _title block_list = let filename = Link.Path.as_filename ~config url in let content (ppf : Format.formatter) = let renderer = Cmarkit_commonmark.renderer () in - let root_block = Cmarkit.Block.Blocks (block_list, Cmarkit.Meta.none) in + let root_block = + Cmarkit.Block.Blocks (header @ block_list, Cmarkit.Meta.none) + in let doc = Cmarkit.Doc.make root_block in Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) in diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index cb6a0c3f9a..6b0909945c 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -21,7 +21,6 @@ val make : config:Config.t -> url:Odoc_document.Url.Path.t -> - header:Cmarkit.Block.t list -> Cmarkit.Doc.t -> Odoc_document.Renderer.page list -> Odoc_document.Renderer.page diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 305624aad5..1e7fdd409f 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -27,6 +27,7 @@ $ odoc markdown-generate list.odocl -o markdown $ cat markdown/test/Test.md + # Module `Test` ## Section 1 ``` type t = int @@ -41,7 +42,21 @@ module List : sig ... end ``` + $ cat markdown/test/Test-List.md + # Module `Test.List` + ``` + type 'a t = 'a list + ``` + ``` + val head : 'a t -> 'a option + ``` + ``` + val headExn : 'a t -> 'a + ``` + $ cat markdown/test/page.md + # The title + Quick reference for the odoc language rendering markdown ## Title ### Subtitle #### Referenceable title From 6cf048a563eb2d252e251f828fd2ac7d083beea9 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 30 Apr 2025 13:03:55 +0100 Subject: [PATCH 17/53] Make header part of the block list --- src/markdown2/generator.ml | 19 ++++++++++--------- src/markdown2/markdown_page.ml | 6 ++---- src/markdown2/markdown_page.mli | 1 - 3 files changed, 12 insertions(+), 14 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index ff0ad0ef96..d1e7949374 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -470,29 +470,30 @@ module Page = struct and subpages ~config subpages = List.map (include_ ~config) subpages and page ~config p : Odoc_document.Renderer.page = - let { Types.Page.preamble = _; items = i; url; source_anchor } = - Doctree.Labels.disambiguate_page ~enter_subpages:false p - in + (* TODO: I'm not sure if we need to disambiguate the page with Doctree.Labels.disambiguate_page *) let subpages = subpages ~config @@ Doctree.Subpages.compute p in - let resolve = Link.Current url in - let i = Doctree.Shift.compute ~on_sub i in - let header, preamble = Doctree.PageTitle.render_title ?source_anchor p in + let resolve = Link.Current p.url in + let i = Doctree.Shift.compute ~on_sub p.items in + let header, preamble = + Doctree.PageTitle.render_title ?source_anchor:p.source_anchor p + in let header = items ~config ~resolve header in let preamble = items ~config ~resolve preamble in let content = items ~config ~resolve i in let root_block = Md.Block.Blocks (header @ preamble @ content, Md.meta) in let doc = Md.Doc.make root_block in - Markdown_page.make ~config ~url doc subpages + Markdown_page.make ~config ~url:p.url doc subpages and source_page ~config sp = let { Types.Source_page.url; contents = _ } = sp in let resolve = Link.Current sp.url in let title = url.Url.Path.name in - let doc = [ Md.Block.empty ] in let header = items ~config ~resolve (Doctree.PageTitle.render_src_title sp) in - Markdown_page.make_src ~header ~config ~url title doc + (* why empty? *) + let doc = header @ [ Md.Block.empty ] in + Markdown_page.make_src ~config ~url title doc end let render ~(config : Config.t) doc = diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index 9d0de18eaa..e227c919e1 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -24,13 +24,11 @@ let make ~config ~url doc children = in { Odoc_document.Renderer.filename; content; children; path = url } -let make_src ~config ~url ~header _title block_list = +let make_src ~config ~url _title block_list = let filename = Link.Path.as_filename ~config url in let content (ppf : Format.formatter) = let renderer = Cmarkit_commonmark.renderer () in - let root_block = - Cmarkit.Block.Blocks (header @ block_list, Cmarkit.Meta.none) - in + let root_block = Cmarkit.Block.Blocks (block_list, Cmarkit.Meta.none) in let doc = Cmarkit.Doc.make root_block in Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) in diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index 6b0909945c..265dc41ac5 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -28,7 +28,6 @@ val make : val make_src : config:Config.t -> url:Odoc_document.Url.Path.t -> - header:Cmarkit.Block.t list -> string -> Cmarkit.Block.t list -> Odoc_document.Renderer.page From 6f1aea2826f5b058065cdffbb92eba1c075acdca Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 30 Apr 2025 13:32:52 +0100 Subject: [PATCH 18/53] Add subpages in markdown test --- src/markdown2/generator.ml | 8 ++++---- test/integration/markdown.t/page.mld | 4 ++++ test/integration/markdown.t/run.t | 10 ++++++++-- 3 files changed, 16 insertions(+), 6 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index d1e7949374..41ee38a12b 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -147,7 +147,7 @@ let rec block ~config ~resolve l = l in [ - (* TODO: Do we need the list (~tight:false) based on surrounding content or can we always be ~tight:true? *) + (* TODO: Do we need the list ~tight:false based on surrounding content or can we always be ~tight:true? *) Md.Block.List (Md.Block.List'.make ~tight:true list_type list_items, Md.meta); ] @@ -176,11 +176,11 @@ let rec block ~config ~resolve l = (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) in [ code_snippet ] - | Source (lang_tag, s) -> + | Source (lang, s) -> let code_block = s |> source inline_text_only |> List.map (fun s -> (s, Md.meta)) in - let info_string = (lang_tag, Md.meta) in + let info_string = (lang, Md.meta) in let code_snippet = Md.Block.Code_block (Md.Block.Code_block.make ~info_string code_block, Md.meta) @@ -470,7 +470,7 @@ module Page = struct and subpages ~config subpages = List.map (include_ ~config) subpages and page ~config p : Odoc_document.Renderer.page = - (* TODO: I'm not sure if we need to disambiguate the page with Doctree.Labels.disambiguate_page *) + (* TODO: disambiguate the page? *) let subpages = subpages ~config @@ Doctree.Subpages.compute p in let resolve = Link.Current p.url in let i = Doctree.Shift.compute ~on_sub p.items in diff --git a/test/integration/markdown.t/page.mld b/test/integration/markdown.t/page.mld index 1370b972ac..ecb1173b29 100644 --- a/test/integration/markdown.t/page.mld +++ b/test/integration/markdown.t/page.mld @@ -30,6 +30,10 @@ See {{!./test.mli}this page from another package}. See {{!styled}this section} for the syntax of references. +{4 Subpages} + +There's a subpage here {{!test}} and another one {{!test2}} + {3 Lists} - First item diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 1e7fdd409f..880ae079e8 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -4,7 +4,11 @@ $ odoc compile --package test -I . page.mld File "page.mld", line 25, characters 23-34: Warning: '{{!...} ...}' (cross-reference) should not be empty. - File "page.mld", line 121, characters 0-11: + File "page.mld", line 35, characters 23-32: + Warning: '{{!...} ...}' (cross-reference) should not be empty. + File "page.mld", line 35, characters 49-59: + Warning: '{{!...} ...}' (cross-reference) should not be empty. + File "page.mld", line 125, characters 0-11: Warning: Tags are not allowed in pages. $ odoc compile --package test test.cmti $ odoc compile --package test -I . test2.cmti @@ -17,7 +21,7 @@ File "list.mli", line 37, characters 12-19: Warning: Reference to 'head' is ambiguous. Please specify its kind: section-head, val-head. $ odoc link page-page.odoc - File "page.mld", line 81, characters 0-33: + File "page.mld", line 85, characters 0-33: Warning: Failed to resolve reference ./odoc_logo_placeholder.jpg Path 'odoc_logo_placeholder.jpg' not found File "page.mld", line 29, characters 4-49: Warning: Failed to resolve reference ./test.mli Path 'test' not found @@ -72,6 +76,8 @@ See [this function from another library](./Test.md#val-v). See [this page from another package](). See [this section](./#styled) for the syntax of references. + ##### Subpages + There's a subpage here [`Test`](./Test.md) and another one [`Test2`](./Test2.md) #### Lists - First item - Second item From 467d8223b96850cb1da50a4fdfccc671e2475c80 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 30 Apr 2025 15:51:14 +0100 Subject: [PATCH 19/53] Bring back filepath but unsure why --- src/markdown2/generator.ml | 2 ++ src/markdown2/generator.mli | 2 +- src/odoc/bin/main.ml | 4 ++-- 3 files changed, 5 insertions(+), 3 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 41ee38a12b..bf86fbbe7a 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -506,3 +506,5 @@ let render ~(config : Config.t) doc = let inline ~config ~xref_base_uri b = let resolve = Link.Base xref_base_uri in inline ~config ~resolve b + +let filepath ~config url = Link.Path.as_filename ~config url diff --git a/src/markdown2/generator.mli b/src/markdown2/generator.mli index 7cc6ca53dc..8ace3211b1 100644 --- a/src/markdown2/generator.mli +++ b/src/markdown2/generator.mli @@ -3,7 +3,7 @@ val render : Odoc_document.Types.Document.t -> Odoc_document.Renderer.page list -(* val filepath : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t *) +val filepath : config:Config.t -> Odoc_document.Url.Path.t -> Fpath.t val items : config:Config.t -> diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 815519ee9b..cd2203838e 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1317,8 +1317,8 @@ module Odoc_markdown_cmd = Make_renderer (struct let render config _sidebar page = Odoc_markdown.Generator.render ~config page - let filepath _url = failwith "Not implemented" - (* Odoc_html.Generator.filepath ~config:html_config url *) + (* QUESTION: Where is this being used? *) + let filepath config url = Odoc_markdown.Generator.filepath ~config url let extra_args = Term.const { Odoc_markdown.Config.root_url = None } let renderer = { Odoc_document.Renderer.name = "markdown"; render; filepath } From c4ec62482b33c677c55a512bc9eeb94ac7a10b23 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 30 Apr 2025 15:51:59 +0100 Subject: [PATCH 20/53] Add header into markdown with belt test --- test/integration/markdown-with-belt.t/run.t | 54 +++++++++++++++++++++ 1 file changed, 54 insertions(+) diff --git a/test/integration/markdown-with-belt.t/run.t b/test/integration/markdown-with-belt.t/run.t index 0432b67a0f..ef4618f027 100644 --- a/test/integration/markdown-with-belt.t/run.t +++ b/test/integration/markdown-with-belt.t/run.t @@ -18,6 +18,60 @@ 1 directory, 2 files $ cat markdown/Belt/Belt.md + # Module `Belt` + A stdlib shipped with Melange + This stdlib is still in *beta* but we encourage you to try it out and give us feedback. + **Motivation** + The motivation for creating such library is to provide Melange users a better end-to-end user experience, since the original OCaml stdlib was not written with JS in mind. Below is a list of areas this lib aims to improve: + 0. Consistency in name convention: camlCase, and arguments order + 1. Exception thrown functions are all suffixed with *Exn*, e.g, *getExn* + 2. Better performance and smaller code size running on JS platform + **Name Convention** + For higher order functions, it will be suffixed **U** if it takes uncurried callback. + ```ocaml + val forEach : 'a t -> ('a -> unit) -> unit + val forEachU : 'a t -> ('a -> unit [\@u]) -> unit + ``` + In general, uncurried version will be faster, but it may be less familiar to people who have a background in functional programming. + **A special encoding for collection safety** + When we create a collection library for a custom data type we need a way to provide a comparator function. Take *Set* for example, suppose its element type is a pair of ints, it needs a custom *compare* function that takes two tuples and returns their order. The *Set* could not just be typed as ` Set.t (int * int) `, its customized *compare* function needs to manifest itself in the signature, otherwise, if the user creates another customized *compare* function, the two collection could mix which would result in runtime error. + The original OCaml stdlib solved the problem using *functor* which creates a big closure at runtime and makes dead code elimination much harder. We use a phantom type to solve the problem: + ```ocaml + module Comparable1 = Belt.Id.MakeComparable (struct + type t = int * int + let cmp (a0, a1) (b0, b1) = + match Pervasives.compare a0 b0 with + | 0 -> Pervasives.compare a1 b1 + | c -> c + end) + + let mySet1 = Belt.Set.make ~id:(module Comparable1) + + module Comparable2 = Belt.Id.MakeComparable (struct + type t = int * int + let cmp (a0, a1) (b0, b1) = + match Pervasives.compare a0 b0 with + | 0 -> Pervasives.compare a1 b1 + | c -> c + end) + + let mySet2 = Belt.Set.make ~id:(module Comparable2) + ``` + Here, the compiler would infer `mySet1` and `mySet2` having different type, so e.g. a \`merge\` operation that tries to merge these two sets will correctly fail. + ```ocaml + val mySet1 : (int * int, Comparable1.identity) t + val mySet2 : (int * int, Comparable2.identity) t + ``` + `Comparable1.identity` and `Comparable2.identity` are not the same using our encoding scheme. + **Collection Hierarchy** + In general, we provide a generic collection module, but also create specialized modules for commonly used data type. Take *Belt.Set* for example, we provide: + ```ocaml + Belt.Set + Belt.Set.Int + Belt.Set.String + ``` + The specialized modules *Belt.Set.Int*, *Belt.Set.String* are in general more efficient. + Currently, both *Belt\_Set* and *Belt.Set* are accessible to users for some technical reasons, we **strongly recommend** users stick to qualified import, *Belt.Set*, we may hide the internal, *i.e*, *Belt\_Set* in the future ``` module Id = Belt_Id ``` From 76be72958bc97489ad050f308656a8e1ca778118 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 11:57:44 +0100 Subject: [PATCH 21/53] Add blank lines on each heading --- src/markdown2/generator.ml | 7 ++--- test/integration/markdown.t/run.t | 44 +++++++++++++++++++++++++++++++ 2 files changed, 48 insertions(+), 3 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index bf86fbbe7a..3a9941063c 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -364,11 +364,13 @@ and items ~config ~resolve l : Md.Block.t list = let content = block ~config ~resolve text in (continue_with [@tailcall]) rest content | Heading h :: rest -> + (* Markdown headings are rendered as a blank line before and after the heading, otherwise it treats it as an inline paragraph *) + let break = Md.Block.Blank_line ("", Md.meta) in let inlines = inline ~config ~resolve h.title in let content = Md.Inline.Inlines (inlines, Md.meta) in let block = Md.Block.Heading.make ~level:(h.level + 1) content in - let heading = [ Md.Block.Heading (block, Md.meta) ] in - (continue_with [@tailcall]) rest heading + let heading_block = Md.Block.Heading (block, Md.meta) in + (continue_with [@tailcall]) rest [ break; heading_block; break ] | Include { attr = _attr; @@ -445,7 +447,6 @@ and documentedSrc ~config ~resolve t = [ block ] | `N n -> to_markdown n in - let block_doc = block ~config ~resolve doc in List.append content block_doc in diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 880ae079e8..421f10b3ef 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -31,13 +31,19 @@ $ odoc markdown-generate list.odocl -o markdown $ cat markdown/test/Test.md + # Module `Test` + + ## Section 1 + ``` type t = int ``` A very important type + ### Section 2 + ``` val v : t ``` @@ -47,7 +53,9 @@ ``` $ cat markdown/test/Test-List.md + # Module `Test.List` + ``` type 'a t = 'a list ``` @@ -59,26 +67,44 @@ ``` $ cat markdown/test/page.md + # The title + Quick reference for the odoc language rendering markdown + ## Title + + ### Subtitle + + #### Referenceable title + See [Referenceable title](./#my_id). + #### Styled + **bold** text, *italic* text, *emphasized* text H2O and 1st + #### Link + Here is a link: [https://www.example.com](https://www.example.com). You can also click [here](https://www.example.com). + #### References + See an empty reference [`Test.v`](./Test.md#val-v). See [this function from another library](./Test.md#val-v). See [this page from another package](). See [this section](./#styled) for the syntax of references. + ##### Subpages + There's a subpage here [`Test`](./Test.md) and another one [`Test2`](./Test2.md) + #### Lists + - First item - Second item 0. First ordered item @@ -89,7 +115,9 @@ 0. First numbered item 1. Second numbered item 2. can also be used + #### Code blocks + Inline `code`. ```ocaml let _ = "Block code" @@ -100,31 +128,45 @@ ```python [i+1 for i in xrange(2)] ``` + #### Verbatim + ``` verbatim text ``` + #### Math + For inline math: `\sqrt 2`. For display math: ``` \sqrt 2 ``` + #### Images + ![./odoc\_logo\_placeholder.jpg]() ![https://picsum.photos/200/100](https://picsum.photos/200/100) + #### Table + + ##### Explicit syntax + \| Header 1 \| Header 2 \| \| --- \| --- \| \| Cell 1 \| Cell 2 \| \| Cell 3 \| Cell 4 \| + ##### Light syntax + \| Header 1 \| Header 2 \| \| --- \| --- \| \| Cell 1 \| Cell 2 \| \| Cell 3 \| Cell 4 \| + #### HTML + This is a strong tag: Odoc language lack support for quotation! @@ -134,6 +176,8 @@ + #### Tags + since 4\.08 Tags are explained in this section. From 563d06255125969f416a038595a7681b99c00380 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 12:01:57 +0100 Subject: [PATCH 22/53] ol start at 1 --- src/markdown2/generator.ml | 2 +- test/integration/markdown.t/run.t | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 3a9941063c..f8795f9727 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -135,7 +135,7 @@ let rec block ~config ~resolve l = | List (typ, l) -> let list_type = match typ with - | Ordered -> `Ordered (0, '.') + | Ordered -> `Ordered (1, '.') | Unordered -> `Unordered '-' in let list_items = diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 421f10b3ef..6a5e9f17e9 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -107,14 +107,14 @@ - First item - Second item - 0. First ordered item - 1. Second numbered item + 1. First ordered item + 2. Second numbered item - First item - Second item - can also be used - 0. First numbered item - 1. Second numbered item - 2. can also be used + 1. First numbered item + 2. Second numbered item + 3. can also be used #### Code blocks From 12e45c7e6961bc7a914430e9f5e67fb21a812d18 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 12:07:25 +0100 Subject: [PATCH 23/53] Remove emph level --- src/markdown2/generator.ml | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index f8795f9727..bfde129dd5 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -17,8 +17,7 @@ let source fn (t : Types.Source.t) = and tokens t = List.concat_map token t in tokens t -(* TODO: What's emph_level? *) -and styled style ~emph_level:_ content = +and styled style content = match style with | `Bold -> let inlines_as_one_inline = Md.Inline.Inlines (content, Md.meta) in @@ -60,7 +59,7 @@ and block_text_only blocks : string list = | _ -> []) blocks -and inline ~config ?(emph_level = 0) ~resolve l = +and inline ~config ~resolve l = let one (t : Types.Inline.one) = match t.desc with | Text s -> [ Md.Inline.Text (s, Md.meta) ] @@ -72,10 +71,10 @@ and inline ~config ?(emph_level = 0) ~resolve l = let break = Md.Inline.Break.make `Hard in [ Md.Inline.Break (break, Md.meta) ] | Styled (style, c) -> - let inline_content = inline ~config ~emph_level ~resolve c in - styled ~emph_level style inline_content + let inline_content = inline ~config ~resolve c in + styled style inline_content | Link { target = External href; content; _ } -> - let inline_content = inline ~config ~emph_level ~resolve content in + let inline_content = inline ~config ~resolve content in let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in let link_definition = Md.Link_definition.make ~dest:(href, Md.meta) () @@ -94,7 +93,7 @@ and inline ~config ?(emph_level = 0) ~resolve l = (* TODO: What's unresolved? A non-existing page/link? Do we want to raise or empty? *) ("", Md.meta) in - let inline_content = inline ~config ~emph_level ~resolve content in + let inline_content = inline ~config ~resolve content in let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in let link_definition = Md.Link_definition.make ~dest:href () in let link_reference = `Inline (link_definition, Md.meta) in From cc601b924d870f8b2c6d24a6802f22e3101457c1 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 12:18:40 +0100 Subject: [PATCH 24/53] Add blank lines after each paragraph --- src/markdown2/generator.ml | 9 +++++---- test/integration/markdown.t/page.mld | 14 ++++++++++++++ test/integration/markdown.t/run.t | 28 ++++++++++++++++++++++++++++ 3 files changed, 47 insertions(+), 4 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index bfde129dd5..2742b1fea0 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -67,7 +67,7 @@ and inline ~config ~resolve l = (* In CommonMark, HTML entities are supported directly, so we can just output them as text *) [ Md.Inline.Text (s, Md.meta) ] | Linebreak -> - (* In CommonMark, a hard line break can be represented by a backslash followed by a newline or by two or more spaces at the end of a line. We use a hard break *) + (* In CommonMark, a line break can be represented by a backslash followed by a newline or by two or more spaces at the end of a line. We use a hard break *) let break = Md.Inline.Break.make `Hard in [ Md.Inline.Break (break, Md.meta) ] | Styled (style, c) -> @@ -86,7 +86,6 @@ and inline ~config ~resolve l = let href = match internal with | Resolved uri -> - (* TODO: Maybe internal links should be relative? *) let url = Link.href ~config ~resolve uri in (url, Md.meta) | Unresolved -> @@ -100,7 +99,7 @@ and inline ~config ~resolve l = let inline_link = Md.Inline.Link.make link_inline link_reference in [ Md.Inline.Link (inline_link, Md.meta) ] | Source c -> - (* CommonMark doesn't allow any complex node inside inline text, right now rendering inline nodes as text *) + (* CommonMark doesn't allow any complex node inside inline text, rendering inline nodes as text *) let content = String.concat ~sep:"" (source inline_text_only c) in [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] | Math s -> @@ -130,7 +129,9 @@ let rec block ~config ~resolve l = let paragraph_block = Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) in - [ paragraph_block ] + (* CommonMark treats paragraph as a block, to align the behavior with other generators such as HTML, we add a blank line after it *) + let break = Md.Block.Blank_line ("", Md.meta) in + [ paragraph_block; break ] | List (typ, l) -> let list_type = match typ with diff --git a/test/integration/markdown.t/page.mld b/test/integration/markdown.t/page.mld index ecb1173b29..25d4dc34e1 100644 --- a/test/integration/markdown.t/page.mld +++ b/test/integration/markdown.t/page.mld @@ -124,3 +124,17 @@ This is a strong tag: {%html: Odoc language lack support for quotation! @since 4.08 Tags are explained in this section. + +{3 Break lines} + +{b Motivation} + +The motivation for creating such library is to provide Melange users a +better end-to-end user experience, since the original OCaml stdlib was not +written with JS in mind. Below is a list of areas this lib aims to +improve: +{ol +{- Consistency in name convention: camlCase, and arguments order} +{- Exception thrown functions are all suffixed with {i Exn}, e.g, {i getExn}} +{- Better performance and smaller code size running on JS platform} +} diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 6a5e9f17e9..42cc1154d1 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -42,12 +42,14 @@ ``` A very important type + ### Section 2 ``` val v : t ``` A very important value + ``` module List : sig ... end ``` @@ -72,6 +74,7 @@ Quick reference for the odoc language rendering markdown + ## Title @@ -82,27 +85,37 @@ See [Referenceable title](./#my_id). + #### Styled **bold** text, *italic* text, *emphasized* text + H2O and 1st + #### Link Here is a link: [https://www.example.com](https://www.example.com). + You can also click [here](https://www.example.com). + #### References See an empty reference [`Test.v`](./Test.md#val-v). + See [this function from another library](./Test.md#val-v). + See [this page from another package](). + See [this section](./#styled) for the syntax of references. + ##### Subpages There's a subpage here [`Test`](./Test.md) and another one [`Test2`](./Test2.md) + #### Lists - First item @@ -119,6 +132,7 @@ #### Code blocks Inline `code`. + ```ocaml let _ = "Block code" ``` @@ -138,7 +152,9 @@ #### Math For inline math: `\sqrt 2`. + For display math: + ``` \sqrt 2 ``` @@ -170,6 +186,7 @@ This is a strong tag: Odoc language lack support for quotation! +
Odoc language lack support for quotation! @@ -181,3 +198,14 @@ since 4\.08 Tags are explained in this section. + + + #### Break lines + + **Motivation** + + The motivation for creating such library is to provide Melange users a better end-to-end user experience, since the original OCaml stdlib was not written with JS in mind. Below is a list of areas this lib aims to improve: + + 1. Consistency in name convention: camlCase, and arguments order + 2. Exception thrown functions are all suffixed with *Exn*, e.g, *getExn* + 3. Better performance and smaller code size running on JS platform From 9707a7a3d5b89d99066ba079288956a2645ebec1 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 12:21:36 +0100 Subject: [PATCH 25/53] Remove useless comment on Linebreak --- src/markdown2/generator.ml | 1 - 1 file changed, 1 deletion(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 2742b1fea0..07f6aec093 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -67,7 +67,6 @@ and inline ~config ~resolve l = (* In CommonMark, HTML entities are supported directly, so we can just output them as text *) [ Md.Inline.Text (s, Md.meta) ] | Linebreak -> - (* In CommonMark, a line break can be represented by a backslash followed by a newline or by two or more spaces at the end of a line. We use a hard break *) let break = Md.Inline.Break.make `Hard in [ Md.Inline.Break (break, Md.meta) ] | Styled (style, c) -> From 32f1d65a39847de6ae980ae12df2cfb5232b760d Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 12:30:45 +0100 Subject: [PATCH 26/53] Remove generate source comment for markdown --- src/odoc/bin/main.ml | 1 - 1 file changed, 1 deletion(-) diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index cd2203838e..9faba43a6a 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1721,7 +1721,6 @@ let () = Odoc_html.generate ~docs:section_pipeline; Odoc_html.generate_source ~docs:section_pipeline; Odoc_markdown_cmd.generate ~docs:section_pipeline; - (* TODO: Do this Odoc_markdown_cmd.generate_source ~docs:section_pipeline; *) Odoc_html.generate_asset ~docs:section_pipeline; Support_files_command.(cmd, info ~docs:section_pipeline); Compile_impl.(cmd, info ~docs:section_pipeline); From faee0dcd2d471aaf9bd2991b907e7c7ce1720bce Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 12:33:59 +0100 Subject: [PATCH 27/53] Remove linebreak test --- test/integration/markdown.t/page.mld | 14 -------------- test/integration/markdown.t/run.t | 11 ----------- 2 files changed, 25 deletions(-) diff --git a/test/integration/markdown.t/page.mld b/test/integration/markdown.t/page.mld index 25d4dc34e1..ecb1173b29 100644 --- a/test/integration/markdown.t/page.mld +++ b/test/integration/markdown.t/page.mld @@ -124,17 +124,3 @@ This is a strong tag: {%html: Odoc language lack support for quotation! @since 4.08 Tags are explained in this section. - -{3 Break lines} - -{b Motivation} - -The motivation for creating such library is to provide Melange users a -better end-to-end user experience, since the original OCaml stdlib was not -written with JS in mind. Below is a list of areas this lib aims to -improve: -{ol -{- Consistency in name convention: camlCase, and arguments order} -{- Exception thrown functions are all suffixed with {i Exn}, e.g, {i getExn}} -{- Better performance and smaller code size running on JS platform} -} diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 42cc1154d1..2bc2ea6c5e 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -198,14 +198,3 @@ since 4\.08 Tags are explained in this section. - - - #### Break lines - - **Motivation** - - The motivation for creating such library is to provide Melange users a better end-to-end user experience, since the original OCaml stdlib was not written with JS in mind. Below is a list of areas this lib aims to improve: - - 1. Consistency in name convention: camlCase, and arguments order - 2. Exception thrown functions are all suffixed with *Exn*, e.g, *getExn* - 3. Better performance and smaller code size running on JS platform From d03bd566013841bcc83af9d964859f1aa8a30324 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 1 May 2025 15:41:50 +0100 Subject: [PATCH 28/53] Add source_page and add a comment about untested --- src/markdown2/generator.ml | 42 +++++++++++++++++++++++++++++++++++--- 1 file changed, 39 insertions(+), 3 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 07f6aec093..6842c327a8 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -485,14 +485,50 @@ module Page = struct Markdown_page.make ~config ~url:p.url doc subpages and source_page ~config sp = - let { Types.Source_page.url; contents = _ } = sp in + (* TODO: source_page isn't tested in markdown2 *) + let { Types.Source_page.url; contents; _ } = sp in let resolve = Link.Current sp.url in let title = url.Url.Path.name in let header = items ~config ~resolve (Doctree.PageTitle.render_src_title sp) in - (* why empty? *) - let doc = header @ [ Md.Block.empty ] in + let markdown_of_doc ~config ~resolve docs = + let rec doc_to_markdown doc = + match doc with + | Types.Source_page.Plain_code s -> + let plain_code = + Md.Block.Code_block + (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) + in + [ plain_code ] + | Tagged_code (info, docs) -> ( + let childrens = List.concat_map doc_to_markdown docs in + match info with + | Syntax tok -> + let syntax = + Md.Block.Code_block + (Md.Block.Code_block.make [ (tok, Md.meta) ], Md.meta) + in + [ syntax; Md.Block.Blocks (childrens, Md.meta) ] + | Link { documentation = _; implementation = None } -> childrens + | Link { documentation = _; implementation = Some anchor } -> + let name = anchor.page.name in + let inline_name = Md.Inline.Text (name, Md.meta) in + let href = Link.href ~config ~resolve anchor in + let link_definition = + Md.Link_definition.make ~dest:(href, Md.meta) () + in + let link_reference = `Inline (link_definition, Md.meta) in + let inline_link = + Md.Inline.Link.make inline_name link_reference + in + let _ = [ Md.Inline.Link (inline_link, Md.meta) ] in + childrens + | Anchor _lbl -> childrens) + in + List.concat_map doc_to_markdown docs + in + let doc = header @ markdown_of_doc ~config ~resolve contents in Markdown_page.make_src ~config ~url title doc end From 62b23d655d6127d1805908caca772d09042b58a6 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Sat, 3 May 2025 11:43:47 +0100 Subject: [PATCH 29/53] Render inline code snippet when no reference --- src/markdown2/generator.ml | 51 +++++++++++++++++++------------------- 1 file changed, 25 insertions(+), 26 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 6842c327a8..9e2d38e3bb 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -59,7 +59,7 @@ and block_text_only blocks : string list = | _ -> []) blocks -and inline ~config ~resolve l = +and inline ~(config : Config.t) ~resolve l = let one (t : Types.Inline.one) = match t.desc with | Text s -> [ Md.Inline.Text (s, Md.meta) ] @@ -72,31 +72,7 @@ and inline ~config ~resolve l = | Styled (style, c) -> let inline_content = inline ~config ~resolve c in styled style inline_content - | Link { target = External href; content; _ } -> - let inline_content = inline ~config ~resolve content in - let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in - let link_definition = - Md.Link_definition.make ~dest:(href, Md.meta) () - in - let link_reference = `Inline (link_definition, Md.meta) in - let inline_link = Md.Inline.Link.make link_inline link_reference in - [ Md.Inline.Link (inline_link, Md.meta) ] - | Link { target = Internal internal; content; _ } -> - let href = - match internal with - | Resolved uri -> - let url = Link.href ~config ~resolve uri in - (url, Md.meta) - | Unresolved -> - (* TODO: What's unresolved? A non-existing page/link? Do we want to raise or empty? *) - ("", Md.meta) - in - let inline_content = inline ~config ~resolve content in - let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in - let link_definition = Md.Link_definition.make ~dest:href () in - let link_reference = `Inline (link_definition, Md.meta) in - let inline_link = Md.Inline.Link.make link_inline link_reference in - [ Md.Inline.Link (inline_link, Md.meta) ] + | Link link -> inline_link ~config ~resolve link | Source c -> (* CommonMark doesn't allow any complex node inside inline text, rendering inline nodes as text *) let content = String.concat ~sep:"" (source inline_text_only c) in @@ -119,6 +95,29 @@ and inline ~config ~resolve l = in List.concat_map one l +and inline_link ~config ~resolve link = + let href = + match link.target with + | External href -> Some href + | Internal internal -> ( + match internal with + | Resolved uri -> Some (Link.href ~config ~resolve uri) + | Unresolved -> + (* TODO: What's unresolved? A non-existing page/link? Do we want to raise or empty? *) + None) + in + match href with + | Some href -> + let inline_content = inline ~config ~resolve link.content in + let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in + let link_definition = Md.Link_definition.make ~dest:(href, Md.meta) () in + let link_reference = `Inline (link_definition, Md.meta) in + let inline_link = Md.Inline.Link.make link_inline link_reference in + [ Md.Inline.Link (inline_link, Md.meta) ] + | None -> + let content = String.concat ~sep:"" (inline_text_only link.content) in + [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] + let rec block ~config ~resolve l = let one (t : Types.Block.one) = match t.desc with From bc3a307c1ae39016604687eb7e0ed9833b34b866 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 14:39:35 +0200 Subject: [PATCH 30/53] Remove comment for unresolved --- src/markdown2/generator.ml | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 9e2d38e3bb..fd7e28b594 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -102,9 +102,7 @@ and inline_link ~config ~resolve link = | Internal internal -> ( match internal with | Resolved uri -> Some (Link.href ~config ~resolve uri) - | Unresolved -> - (* TODO: What's unresolved? A non-existing page/link? Do we want to raise or empty? *) - None) + | Unresolved -> None) in match href with | Some href -> From 8e2667e45b1ff7b018478c8631fba4457b896cf9 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 14:39:58 +0200 Subject: [PATCH 31/53] Update snapshots --- test/integration/markdown-with-belt.t/run.t | 26 ++++++++++++++++++--- test/integration/markdown.t/run.t | 2 +- 2 files changed, 24 insertions(+), 4 deletions(-) diff --git a/test/integration/markdown-with-belt.t/run.t b/test/integration/markdown-with-belt.t/run.t index ef4618f027..419db6aa24 100644 --- a/test/integration/markdown-with-belt.t/run.t +++ b/test/integration/markdown-with-belt.t/run.t @@ -18,24 +18,36 @@ 1 directory, 2 files $ cat markdown/Belt/Belt.md + # Module `Belt` + A stdlib shipped with Melange + This stdlib is still in *beta* but we encourage you to try it out and give us feedback. + **Motivation** + The motivation for creating such library is to provide Melange users a better end-to-end user experience, since the original OCaml stdlib was not written with JS in mind. Below is a list of areas this lib aims to improve: - 0. Consistency in name convention: camlCase, and arguments order - 1. Exception thrown functions are all suffixed with *Exn*, e.g, *getExn* - 2. Better performance and smaller code size running on JS platform + + 1. Consistency in name convention: camlCase, and arguments order + 2. Exception thrown functions are all suffixed with *Exn*, e.g, *getExn* + 3. Better performance and smaller code size running on JS platform **Name Convention** + For higher order functions, it will be suffixed **U** if it takes uncurried callback. + ```ocaml val forEach : 'a t -> ('a -> unit) -> unit val forEachU : 'a t -> ('a -> unit [\@u]) -> unit ``` In general, uncurried version will be faster, but it may be less familiar to people who have a background in functional programming. + **A special encoding for collection safety** + When we create a collection library for a custom data type we need a way to provide a comparator function. Take *Set* for example, suppose its element type is a pair of ints, it needs a custom *compare* function that takes two tuples and returns their order. The *Set* could not just be typed as ` Set.t (int * int) `, its customized *compare* function needs to manifest itself in the signature, otherwise, if the user creates another customized *compare* function, the two collection could mix which would result in runtime error. + The original OCaml stdlib solved the problem using *functor* which creates a big closure at runtime and makes dead code elimination much harder. We use a phantom type to solve the problem: + ```ocaml module Comparable1 = Belt.Id.MakeComparable (struct type t = int * int @@ -58,23 +70,31 @@ let mySet2 = Belt.Set.make ~id:(module Comparable2) ``` Here, the compiler would infer `mySet1` and `mySet2` having different type, so e.g. a \`merge\` operation that tries to merge these two sets will correctly fail. + ```ocaml val mySet1 : (int * int, Comparable1.identity) t val mySet2 : (int * int, Comparable2.identity) t ``` `Comparable1.identity` and `Comparable2.identity` are not the same using our encoding scheme. + **Collection Hierarchy** + In general, we provide a generic collection module, but also create specialized modules for commonly used data type. Take *Belt.Set* for example, we provide: + ```ocaml Belt.Set Belt.Set.Int Belt.Set.String ``` The specialized modules *Belt.Set.Int*, *Belt.Set.String* are in general more efficient. + Currently, both *Belt\_Set* and *Belt.Set* are accessible to users for some technical reasons, we **strongly recommend** users stick to qualified import, *Belt.Set*, we may hide the internal, *i.e*, *Belt\_Set* in the future + ``` module Id = Belt_Id ``` [`Belt.Id`](./Belt_Id.md) + Provide utilities to create identified comparators or hashes for data structures used below. + It create a unique identifier per module of functions so that different data structures with slightly different comparison functions won't mix diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 2bc2ea6c5e..862a73f097 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -106,7 +106,7 @@ See [this function from another library](./Test.md#val-v). - See [this page from another package](). + See `this page from another package`. See [this section](./#styled) for the syntax of references. From e1cd5e292bf2adf934ecf5af58d782c48b551149 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 14:44:24 +0200 Subject: [PATCH 32/53] First effort --- src/markdown2/config.ml | 4 +- src/markdown2/data_uchar.ml | 652 +++++++++++ src/markdown2/dune | 2 +- src/markdown2/generator.ml | 5 +- src/markdown2/generator.mli | 4 +- src/markdown2/markdown_page.ml | 12 +- src/markdown2/markdown_page.mli | 4 +- src/markdown2/renderer.ml | 1797 +++++++++++++++++++++++++++++++ src/odoc/bin/main.ml | 3 +- 9 files changed, 2467 insertions(+), 16 deletions(-) create mode 100644 src/markdown2/data_uchar.ml create mode 100644 src/markdown2/renderer.ml diff --git a/src/markdown2/config.ml b/src/markdown2/config.ml index cb104e601c..af437d2fe3 100644 --- a/src/markdown2/config.ml +++ b/src/markdown2/config.ml @@ -1,5 +1,5 @@ (* Markdown output configuration *) -type t = { root_url : string option } +type t = { root_url : string option; allow_html : bool } -let v ~root_url () = { root_url } +let make ~root_url ~allow_html () = { root_url; allow_html } diff --git a/src/markdown2/data_uchar.ml b/src/markdown2/data_uchar.ml new file mode 100644 index 0000000000..ac10a5ec31 --- /dev/null +++ b/src/markdown2/data_uchar.ml @@ -0,0 +1,652 @@ +(*--------------------------------------------------------------------------- + Copyright (c) 2024 The cmarkit programmers. All rights reserved. + SPDX-License-Identifier: ISC + ---------------------------------------------------------------------------*) + + +let unicode_version = "16.0.0" + +let [@ocamlformat "disable"] whitespace = + [|0x0009; 0x000A; 0x000C; 0x000D; 0x0020; 0x00A0; 0x1680; 0x2000; 0x2001; + 0x2002; 0x2003; 0x2004; 0x2005; 0x2006; 0x2007; 0x2008; 0x2009; 0x200A; + 0x202F; 0x205F; 0x3000|] + +let [@ocamlformat "disable"] punctuation = + [|0x0021; 0x0022; 0x0023; 0x0024; 0x0025; 0x0026; 0x0027; 0x0028; 0x0029; + 0x002A; 0x002B; 0x002C; 0x002D; 0x002E; 0x002F; 0x003A; 0x003B; 0x003C; + 0x003D; 0x003E; 0x003F; 0x0040; 0x005B; 0x005C; 0x005D; 0x005E; 0x005F; + 0x0060; 0x007B; 0x007C; 0x007D; 0x007E; 0x00A1; 0x00A7; 0x00AB; 0x00B6; + 0x00B7; 0x00BB; 0x00BF; 0x037E; 0x0387; 0x055A; 0x055B; 0x055C; 0x055D; + 0x055E; 0x055F; 0x0589; 0x058A; 0x05BE; 0x05C0; 0x05C3; 0x05C6; 0x05F3; + 0x05F4; 0x0609; 0x060A; 0x060C; 0x060D; 0x061B; 0x061D; 0x061E; 0x061F; + 0x066A; 0x066B; 0x066C; 0x066D; 0x06D4; 0x0700; 0x0701; 0x0702; 0x0703; + 0x0704; 0x0705; 0x0706; 0x0707; 0x0708; 0x0709; 0x070A; 0x070B; 0x070C; + 0x070D; 0x07F7; 0x07F8; 0x07F9; 0x0830; 0x0831; 0x0832; 0x0833; 0x0834; + 0x0835; 0x0836; 0x0837; 0x0838; 0x0839; 0x083A; 0x083B; 0x083C; 0x083D; + 0x083E; 0x085E; 0x0964; 0x0965; 0x0970; 0x09FD; 0x0A76; 0x0AF0; 0x0C77; + 0x0C84; 0x0DF4; 0x0E4F; 0x0E5A; 0x0E5B; 0x0F04; 0x0F05; 0x0F06; 0x0F07; + 0x0F08; 0x0F09; 0x0F0A; 0x0F0B; 0x0F0C; 0x0F0D; 0x0F0E; 0x0F0F; 0x0F10; + 0x0F11; 0x0F12; 0x0F14; 0x0F3A; 0x0F3B; 0x0F3C; 0x0F3D; 0x0F85; 0x0FD0; + 0x0FD1; 0x0FD2; 0x0FD3; 0x0FD4; 0x0FD9; 0x0FDA; 0x104A; 0x104B; 0x104C; + 0x104D; 0x104E; 0x104F; 0x10FB; 0x1360; 0x1361; 0x1362; 0x1363; 0x1364; + 0x1365; 0x1366; 0x1367; 0x1368; 0x1400; 0x166E; 0x169B; 0x169C; 0x16EB; + 0x16EC; 0x16ED; 0x1735; 0x1736; 0x17D4; 0x17D5; 0x17D6; 0x17D8; 0x17D9; + 0x17DA; 0x1800; 0x1801; 0x1802; 0x1803; 0x1804; 0x1805; 0x1806; 0x1807; + 0x1808; 0x1809; 0x180A; 0x1944; 0x1945; 0x1A1E; 0x1A1F; 0x1AA0; 0x1AA1; + 0x1AA2; 0x1AA3; 0x1AA4; 0x1AA5; 0x1AA6; 0x1AA8; 0x1AA9; 0x1AAA; 0x1AAB; + 0x1AAC; 0x1AAD; 0x1B4E; 0x1B4F; 0x1B5A; 0x1B5B; 0x1B5C; 0x1B5D; 0x1B5E; + 0x1B5F; 0x1B60; 0x1B7D; 0x1B7E; 0x1B7F; 0x1BFC; 0x1BFD; 0x1BFE; 0x1BFF; + 0x1C3B; 0x1C3C; 0x1C3D; 0x1C3E; 0x1C3F; 0x1C7E; 0x1C7F; 0x1CC0; 0x1CC1; + 0x1CC2; 0x1CC3; 0x1CC4; 0x1CC5; 0x1CC6; 0x1CC7; 0x1CD3; 0x2010; 0x2011; + 0x2012; 0x2013; 0x2014; 0x2015; 0x2016; 0x2017; 0x2018; 0x2019; 0x201A; + 0x201B; 0x201C; 0x201D; 0x201E; 0x201F; 0x2020; 0x2021; 0x2022; 0x2023; + 0x2024; 0x2025; 0x2026; 0x2027; 0x2030; 0x2031; 0x2032; 0x2033; 0x2034; + 0x2035; 0x2036; 0x2037; 0x2038; 0x2039; 0x203A; 0x203B; 0x203C; 0x203D; + 0x203E; 0x203F; 0x2040; 0x2041; 0x2042; 0x2043; 0x2045; 0x2046; 0x2047; + 0x2048; 0x2049; 0x204A; 0x204B; 0x204C; 0x204D; 0x204E; 0x204F; 0x2050; + 0x2051; 0x2053; 0x2054; 0x2055; 0x2056; 0x2057; 0x2058; 0x2059; 0x205A; + 0x205B; 0x205C; 0x205D; 0x205E; 0x207D; 0x207E; 0x208D; 0x208E; 0x2308; + 0x2309; 0x230A; 0x230B; 0x2329; 0x232A; 0x2768; 0x2769; 0x276A; 0x276B; + 0x276C; 0x276D; 0x276E; 0x276F; 0x2770; 0x2771; 0x2772; 0x2773; 0x2774; + 0x2775; 0x27C5; 0x27C6; 0x27E6; 0x27E7; 0x27E8; 0x27E9; 0x27EA; 0x27EB; + 0x27EC; 0x27ED; 0x27EE; 0x27EF; 0x2983; 0x2984; 0x2985; 0x2986; 0x2987; + 0x2988; 0x2989; 0x298A; 0x298B; 0x298C; 0x298D; 0x298E; 0x298F; 0x2990; + 0x2991; 0x2992; 0x2993; 0x2994; 0x2995; 0x2996; 0x2997; 0x2998; 0x29D8; + 0x29D9; 0x29DA; 0x29DB; 0x29FC; 0x29FD; 0x2CF9; 0x2CFA; 0x2CFB; 0x2CFC; + 0x2CFE; 0x2CFF; 0x2D70; 0x2E00; 0x2E01; 0x2E02; 0x2E03; 0x2E04; 0x2E05; + 0x2E06; 0x2E07; 0x2E08; 0x2E09; 0x2E0A; 0x2E0B; 0x2E0C; 0x2E0D; 0x2E0E; + 0x2E0F; 0x2E10; 0x2E11; 0x2E12; 0x2E13; 0x2E14; 0x2E15; 0x2E16; 0x2E17; + 0x2E18; 0x2E19; 0x2E1A; 0x2E1B; 0x2E1C; 0x2E1D; 0x2E1E; 0x2E1F; 0x2E20; + 0x2E21; 0x2E22; 0x2E23; 0x2E24; 0x2E25; 0x2E26; 0x2E27; 0x2E28; 0x2E29; + 0x2E2A; 0x2E2B; 0x2E2C; 0x2E2D; 0x2E2E; 0x2E30; 0x2E31; 0x2E32; 0x2E33; + 0x2E34; 0x2E35; 0x2E36; 0x2E37; 0x2E38; 0x2E39; 0x2E3A; 0x2E3B; 0x2E3C; + 0x2E3D; 0x2E3E; 0x2E3F; 0x2E40; 0x2E41; 0x2E42; 0x2E43; 0x2E44; 0x2E45; + 0x2E46; 0x2E47; 0x2E48; 0x2E49; 0x2E4A; 0x2E4B; 0x2E4C; 0x2E4D; 0x2E4E; + 0x2E4F; 0x2E52; 0x2E53; 0x2E54; 0x2E55; 0x2E56; 0x2E57; 0x2E58; 0x2E59; + 0x2E5A; 0x2E5B; 0x2E5C; 0x2E5D; 0x3001; 0x3002; 0x3003; 0x3008; 0x3009; + 0x300A; 0x300B; 0x300C; 0x300D; 0x300E; 0x300F; 0x3010; 0x3011; 0x3014; + 0x3015; 0x3016; 0x3017; 0x3018; 0x3019; 0x301A; 0x301B; 0x301C; 0x301D; + 0x301E; 0x301F; 0x3030; 0x303D; 0x30A0; 0x30FB; 0xA4FE; 0xA4FF; 0xA60D; + 0xA60E; 0xA60F; 0xA673; 0xA67E; 0xA6F2; 0xA6F3; 0xA6F4; 0xA6F5; 0xA6F6; + 0xA6F7; 0xA874; 0xA875; 0xA876; 0xA877; 0xA8CE; 0xA8CF; 0xA8F8; 0xA8F9; + 0xA8FA; 0xA8FC; 0xA92E; 0xA92F; 0xA95F; 0xA9C1; 0xA9C2; 0xA9C3; 0xA9C4; + 0xA9C5; 0xA9C6; 0xA9C7; 0xA9C8; 0xA9C9; 0xA9CA; 0xA9CB; 0xA9CC; 0xA9CD; + 0xA9DE; 0xA9DF; 0xAA5C; 0xAA5D; 0xAA5E; 0xAA5F; 0xAADE; 0xAADF; 0xAAF0; + 0xAAF1; 0xABEB; 0xFD3E; 0xFD3F; 0xFE10; 0xFE11; 0xFE12; 0xFE13; 0xFE14; + 0xFE15; 0xFE16; 0xFE17; 0xFE18; 0xFE19; 0xFE30; 0xFE31; 0xFE32; 0xFE33; + 0xFE34; 0xFE35; 0xFE36; 0xFE37; 0xFE38; 0xFE39; 0xFE3A; 0xFE3B; 0xFE3C; + 0xFE3D; 0xFE3E; 0xFE3F; 0xFE40; 0xFE41; 0xFE42; 0xFE43; 0xFE44; 0xFE45; + 0xFE46; 0xFE47; 0xFE48; 0xFE49; 0xFE4A; 0xFE4B; 0xFE4C; 0xFE4D; 0xFE4E; + 0xFE4F; 0xFE50; 0xFE51; 0xFE52; 0xFE54; 0xFE55; 0xFE56; 0xFE57; 0xFE58; + 0xFE59; 0xFE5A; 0xFE5B; 0xFE5C; 0xFE5D; 0xFE5E; 0xFE5F; 0xFE60; 0xFE61; + 0xFE63; 0xFE68; 0xFE6A; 0xFE6B; 0xFF01; 0xFF02; 0xFF03; 0xFF05; 0xFF06; + 0xFF07; 0xFF08; 0xFF09; 0xFF0A; 0xFF0C; 0xFF0D; 0xFF0E; 0xFF0F; 0xFF1A; + 0xFF1B; 0xFF1F; 0xFF20; 0xFF3B; 0xFF3C; 0xFF3D; 0xFF3F; 0xFF5B; 0xFF5D; + 0xFF5F; 0xFF60; 0xFF61; 0xFF62; 0xFF63; 0xFF64; 0xFF65; 0x10100; 0x10101; + 0x10102; 0x1039F; 0x103D0; 0x1056F; 0x10857; 0x1091F; 0x1093F; 0x10A50; + 0x10A51; 0x10A52; 0x10A53; 0x10A54; 0x10A55; 0x10A56; 0x10A57; 0x10A58; + 0x10A7F; 0x10AF0; 0x10AF1; 0x10AF2; 0x10AF3; 0x10AF4; 0x10AF5; 0x10AF6; + 0x10B39; 0x10B3A; 0x10B3B; 0x10B3C; 0x10B3D; 0x10B3E; 0x10B3F; 0x10B99; + 0x10B9A; 0x10B9B; 0x10B9C; 0x10D6E; 0x10EAD; 0x10F55; 0x10F56; 0x10F57; + 0x10F58; 0x10F59; 0x10F86; 0x10F87; 0x10F88; 0x10F89; 0x11047; 0x11048; + 0x11049; 0x1104A; 0x1104B; 0x1104C; 0x1104D; 0x110BB; 0x110BC; 0x110BE; + 0x110BF; 0x110C0; 0x110C1; 0x11140; 0x11141; 0x11142; 0x11143; 0x11174; + 0x11175; 0x111C5; 0x111C6; 0x111C7; 0x111C8; 0x111CD; 0x111DB; 0x111DD; + 0x111DE; 0x111DF; 0x11238; 0x11239; 0x1123A; 0x1123B; 0x1123C; 0x1123D; + 0x112A9; 0x113D4; 0x113D5; 0x113D7; 0x113D8; 0x1144B; 0x1144C; 0x1144D; + 0x1144E; 0x1144F; 0x1145A; 0x1145B; 0x1145D; 0x114C6; 0x115C1; 0x115C2; + 0x115C3; 0x115C4; 0x115C5; 0x115C6; 0x115C7; 0x115C8; 0x115C9; 0x115CA; + 0x115CB; 0x115CC; 0x115CD; 0x115CE; 0x115CF; 0x115D0; 0x115D1; 0x115D2; + 0x115D3; 0x115D4; 0x115D5; 0x115D6; 0x115D7; 0x11641; 0x11642; 0x11643; + 0x11660; 0x11661; 0x11662; 0x11663; 0x11664; 0x11665; 0x11666; 0x11667; + 0x11668; 0x11669; 0x1166A; 0x1166B; 0x1166C; 0x116B9; 0x1173C; 0x1173D; + 0x1173E; 0x1183B; 0x11944; 0x11945; 0x11946; 0x119E2; 0x11A3F; 0x11A40; + 0x11A41; 0x11A42; 0x11A43; 0x11A44; 0x11A45; 0x11A46; 0x11A9A; 0x11A9B; + 0x11A9C; 0x11A9E; 0x11A9F; 0x11AA0; 0x11AA1; 0x11AA2; 0x11B00; 0x11B01; + 0x11B02; 0x11B03; 0x11B04; 0x11B05; 0x11B06; 0x11B07; 0x11B08; 0x11B09; + 0x11BE1; 0x11C41; 0x11C42; 0x11C43; 0x11C44; 0x11C45; 0x11C70; 0x11C71; + 0x11EF7; 0x11EF8; 0x11F43; 0x11F44; 0x11F45; 0x11F46; 0x11F47; 0x11F48; + 0x11F49; 0x11F4A; 0x11F4B; 0x11F4C; 0x11F4D; 0x11F4E; 0x11F4F; 0x11FFF; + 0x12470; 0x12471; 0x12472; 0x12473; 0x12474; 0x12FF1; 0x12FF2; 0x16A6E; + 0x16A6F; 0x16AF5; 0x16B37; 0x16B38; 0x16B39; 0x16B3A; 0x16B3B; 0x16B44; + 0x16D6D; 0x16D6E; 0x16D6F; 0x16E97; 0x16E98; 0x16E99; 0x16E9A; 0x16FE2; + 0x1BC9F; 0x1DA87; 0x1DA88; 0x1DA89; 0x1DA8A; 0x1DA8B; 0x1E5FF; 0x1E95E; + 0x1E95F|] + +let case_fold = + [|0x0041, "\u{0061}"; 0x0042, "\u{0062}"; 0x0043, "\u{0063}"; + 0x0044, "\u{0064}"; 0x0045, "\u{0065}"; 0x0046, "\u{0066}"; + 0x0047, "\u{0067}"; 0x0048, "\u{0068}"; 0x0049, "\u{0069}"; + 0x004A, "\u{006A}"; 0x004B, "\u{006B}"; 0x004C, "\u{006C}"; + 0x004D, "\u{006D}"; 0x004E, "\u{006E}"; 0x004F, "\u{006F}"; + 0x0050, "\u{0070}"; 0x0051, "\u{0071}"; 0x0052, "\u{0072}"; + 0x0053, "\u{0073}"; 0x0054, "\u{0074}"; 0x0055, "\u{0075}"; + 0x0056, "\u{0076}"; 0x0057, "\u{0077}"; 0x0058, "\u{0078}"; + 0x0059, "\u{0079}"; 0x005A, "\u{007A}"; 0x00B5, "\u{03BC}"; + 0x00C0, "\u{00E0}"; 0x00C1, "\u{00E1}"; 0x00C2, "\u{00E2}"; + 0x00C3, "\u{00E3}"; 0x00C4, "\u{00E4}"; 0x00C5, "\u{00E5}"; + 0x00C6, "\u{00E6}"; 0x00C7, "\u{00E7}"; 0x00C8, "\u{00E8}"; + 0x00C9, "\u{00E9}"; 0x00CA, "\u{00EA}"; 0x00CB, "\u{00EB}"; + 0x00CC, "\u{00EC}"; 0x00CD, "\u{00ED}"; 0x00CE, "\u{00EE}"; + 0x00CF, "\u{00EF}"; 0x00D0, "\u{00F0}"; 0x00D1, "\u{00F1}"; + 0x00D2, "\u{00F2}"; 0x00D3, "\u{00F3}"; 0x00D4, "\u{00F4}"; + 0x00D5, "\u{00F5}"; 0x00D6, "\u{00F6}"; 0x00D8, "\u{00F8}"; + 0x00D9, "\u{00F9}"; 0x00DA, "\u{00FA}"; 0x00DB, "\u{00FB}"; + 0x00DC, "\u{00FC}"; 0x00DD, "\u{00FD}"; 0x00DE, "\u{00FE}"; + 0x00DF, "\u{0073}\u{0073}"; 0x0100, "\u{0101}"; 0x0102, "\u{0103}"; + 0x0104, "\u{0105}"; 0x0106, "\u{0107}"; 0x0108, "\u{0109}"; + 0x010A, "\u{010B}"; 0x010C, "\u{010D}"; 0x010E, "\u{010F}"; + 0x0110, "\u{0111}"; 0x0112, "\u{0113}"; 0x0114, "\u{0115}"; + 0x0116, "\u{0117}"; 0x0118, "\u{0119}"; 0x011A, "\u{011B}"; + 0x011C, "\u{011D}"; 0x011E, "\u{011F}"; 0x0120, "\u{0121}"; + 0x0122, "\u{0123}"; 0x0124, "\u{0125}"; 0x0126, "\u{0127}"; + 0x0128, "\u{0129}"; 0x012A, "\u{012B}"; 0x012C, "\u{012D}"; + 0x012E, "\u{012F}"; 0x0130, "\u{0069}\u{0307}"; 0x0132, "\u{0133}"; + 0x0134, "\u{0135}"; 0x0136, "\u{0137}"; 0x0139, "\u{013A}"; + 0x013B, "\u{013C}"; 0x013D, "\u{013E}"; 0x013F, "\u{0140}"; + 0x0141, "\u{0142}"; 0x0143, "\u{0144}"; 0x0145, "\u{0146}"; + 0x0147, "\u{0148}"; 0x0149, "\u{02BC}\u{006E}"; 0x014A, "\u{014B}"; + 0x014C, "\u{014D}"; 0x014E, "\u{014F}"; 0x0150, "\u{0151}"; + 0x0152, "\u{0153}"; 0x0154, "\u{0155}"; 0x0156, "\u{0157}"; + 0x0158, "\u{0159}"; 0x015A, "\u{015B}"; 0x015C, "\u{015D}"; + 0x015E, "\u{015F}"; 0x0160, "\u{0161}"; 0x0162, "\u{0163}"; + 0x0164, "\u{0165}"; 0x0166, "\u{0167}"; 0x0168, "\u{0169}"; + 0x016A, "\u{016B}"; 0x016C, "\u{016D}"; 0x016E, "\u{016F}"; + 0x0170, "\u{0171}"; 0x0172, "\u{0173}"; 0x0174, "\u{0175}"; + 0x0176, "\u{0177}"; 0x0178, "\u{00FF}"; 0x0179, "\u{017A}"; + 0x017B, "\u{017C}"; 0x017D, "\u{017E}"; 0x017F, "\u{0073}"; + 0x0181, "\u{0253}"; 0x0182, "\u{0183}"; 0x0184, "\u{0185}"; + 0x0186, "\u{0254}"; 0x0187, "\u{0188}"; 0x0189, "\u{0256}"; + 0x018A, "\u{0257}"; 0x018B, "\u{018C}"; 0x018E, "\u{01DD}"; + 0x018F, "\u{0259}"; 0x0190, "\u{025B}"; 0x0191, "\u{0192}"; + 0x0193, "\u{0260}"; 0x0194, "\u{0263}"; 0x0196, "\u{0269}"; + 0x0197, "\u{0268}"; 0x0198, "\u{0199}"; 0x019C, "\u{026F}"; + 0x019D, "\u{0272}"; 0x019F, "\u{0275}"; 0x01A0, "\u{01A1}"; + 0x01A2, "\u{01A3}"; 0x01A4, "\u{01A5}"; 0x01A6, "\u{0280}"; + 0x01A7, "\u{01A8}"; 0x01A9, "\u{0283}"; 0x01AC, "\u{01AD}"; + 0x01AE, "\u{0288}"; 0x01AF, "\u{01B0}"; 0x01B1, "\u{028A}"; + 0x01B2, "\u{028B}"; 0x01B3, "\u{01B4}"; 0x01B5, "\u{01B6}"; + 0x01B7, "\u{0292}"; 0x01B8, "\u{01B9}"; 0x01BC, "\u{01BD}"; + 0x01C4, "\u{01C6}"; 0x01C5, "\u{01C6}"; 0x01C7, "\u{01C9}"; + 0x01C8, "\u{01C9}"; 0x01CA, "\u{01CC}"; 0x01CB, "\u{01CC}"; + 0x01CD, "\u{01CE}"; 0x01CF, "\u{01D0}"; 0x01D1, "\u{01D2}"; + 0x01D3, "\u{01D4}"; 0x01D5, "\u{01D6}"; 0x01D7, "\u{01D8}"; + 0x01D9, "\u{01DA}"; 0x01DB, "\u{01DC}"; 0x01DE, "\u{01DF}"; + 0x01E0, "\u{01E1}"; 0x01E2, "\u{01E3}"; 0x01E4, "\u{01E5}"; + 0x01E6, "\u{01E7}"; 0x01E8, "\u{01E9}"; 0x01EA, "\u{01EB}"; + 0x01EC, "\u{01ED}"; 0x01EE, "\u{01EF}"; 0x01F0, "\u{006A}\u{030C}"; + 0x01F1, "\u{01F3}"; 0x01F2, "\u{01F3}"; 0x01F4, "\u{01F5}"; + 0x01F6, "\u{0195}"; 0x01F7, "\u{01BF}"; 0x01F8, "\u{01F9}"; + 0x01FA, "\u{01FB}"; 0x01FC, "\u{01FD}"; 0x01FE, "\u{01FF}"; + 0x0200, "\u{0201}"; 0x0202, "\u{0203}"; 0x0204, "\u{0205}"; + 0x0206, "\u{0207}"; 0x0208, "\u{0209}"; 0x020A, "\u{020B}"; + 0x020C, "\u{020D}"; 0x020E, "\u{020F}"; 0x0210, "\u{0211}"; + 0x0212, "\u{0213}"; 0x0214, "\u{0215}"; 0x0216, "\u{0217}"; + 0x0218, "\u{0219}"; 0x021A, "\u{021B}"; 0x021C, "\u{021D}"; + 0x021E, "\u{021F}"; 0x0220, "\u{019E}"; 0x0222, "\u{0223}"; + 0x0224, "\u{0225}"; 0x0226, "\u{0227}"; 0x0228, "\u{0229}"; + 0x022A, "\u{022B}"; 0x022C, "\u{022D}"; 0x022E, "\u{022F}"; + 0x0230, "\u{0231}"; 0x0232, "\u{0233}"; 0x023A, "\u{2C65}"; + 0x023B, "\u{023C}"; 0x023D, "\u{019A}"; 0x023E, "\u{2C66}"; + 0x0241, "\u{0242}"; 0x0243, "\u{0180}"; 0x0244, "\u{0289}"; + 0x0245, "\u{028C}"; 0x0246, "\u{0247}"; 0x0248, "\u{0249}"; + 0x024A, "\u{024B}"; 0x024C, "\u{024D}"; 0x024E, "\u{024F}"; + 0x0345, "\u{03B9}"; 0x0370, "\u{0371}"; 0x0372, "\u{0373}"; + 0x0376, "\u{0377}"; 0x037F, "\u{03F3}"; 0x0386, "\u{03AC}"; + 0x0388, "\u{03AD}"; 0x0389, "\u{03AE}"; 0x038A, "\u{03AF}"; + 0x038C, "\u{03CC}"; 0x038E, "\u{03CD}"; 0x038F, "\u{03CE}"; + 0x0390, "\u{03B9}\u{0308}\u{0301}"; 0x0391, "\u{03B1}"; + 0x0392, "\u{03B2}"; 0x0393, "\u{03B3}"; 0x0394, "\u{03B4}"; + 0x0395, "\u{03B5}"; 0x0396, "\u{03B6}"; 0x0397, "\u{03B7}"; + 0x0398, "\u{03B8}"; 0x0399, "\u{03B9}"; 0x039A, "\u{03BA}"; + 0x039B, "\u{03BB}"; 0x039C, "\u{03BC}"; 0x039D, "\u{03BD}"; + 0x039E, "\u{03BE}"; 0x039F, "\u{03BF}"; 0x03A0, "\u{03C0}"; + 0x03A1, "\u{03C1}"; 0x03A3, "\u{03C3}"; 0x03A4, "\u{03C4}"; + 0x03A5, "\u{03C5}"; 0x03A6, "\u{03C6}"; 0x03A7, "\u{03C7}"; + 0x03A8, "\u{03C8}"; 0x03A9, "\u{03C9}"; 0x03AA, "\u{03CA}"; + 0x03AB, "\u{03CB}"; 0x03B0, "\u{03C5}\u{0308}\u{0301}"; + 0x03C2, "\u{03C3}"; 0x03CF, "\u{03D7}"; 0x03D0, "\u{03B2}"; + 0x03D1, "\u{03B8}"; 0x03D5, "\u{03C6}"; 0x03D6, "\u{03C0}"; + 0x03D8, "\u{03D9}"; 0x03DA, "\u{03DB}"; 0x03DC, "\u{03DD}"; + 0x03DE, "\u{03DF}"; 0x03E0, "\u{03E1}"; 0x03E2, "\u{03E3}"; + 0x03E4, "\u{03E5}"; 0x03E6, "\u{03E7}"; 0x03E8, "\u{03E9}"; + 0x03EA, "\u{03EB}"; 0x03EC, "\u{03ED}"; 0x03EE, "\u{03EF}"; + 0x03F0, "\u{03BA}"; 0x03F1, "\u{03C1}"; 0x03F4, "\u{03B8}"; + 0x03F5, "\u{03B5}"; 0x03F7, "\u{03F8}"; 0x03F9, "\u{03F2}"; + 0x03FA, "\u{03FB}"; 0x03FD, "\u{037B}"; 0x03FE, "\u{037C}"; + 0x03FF, "\u{037D}"; 0x0400, "\u{0450}"; 0x0401, "\u{0451}"; + 0x0402, "\u{0452}"; 0x0403, "\u{0453}"; 0x0404, "\u{0454}"; + 0x0405, "\u{0455}"; 0x0406, "\u{0456}"; 0x0407, "\u{0457}"; + 0x0408, "\u{0458}"; 0x0409, "\u{0459}"; 0x040A, "\u{045A}"; + 0x040B, "\u{045B}"; 0x040C, "\u{045C}"; 0x040D, "\u{045D}"; + 0x040E, "\u{045E}"; 0x040F, "\u{045F}"; 0x0410, "\u{0430}"; + 0x0411, "\u{0431}"; 0x0412, "\u{0432}"; 0x0413, "\u{0433}"; + 0x0414, "\u{0434}"; 0x0415, "\u{0435}"; 0x0416, "\u{0436}"; + 0x0417, "\u{0437}"; 0x0418, "\u{0438}"; 0x0419, "\u{0439}"; + 0x041A, "\u{043A}"; 0x041B, "\u{043B}"; 0x041C, "\u{043C}"; + 0x041D, "\u{043D}"; 0x041E, "\u{043E}"; 0x041F, "\u{043F}"; + 0x0420, "\u{0440}"; 0x0421, "\u{0441}"; 0x0422, "\u{0442}"; + 0x0423, "\u{0443}"; 0x0424, "\u{0444}"; 0x0425, "\u{0445}"; + 0x0426, "\u{0446}"; 0x0427, "\u{0447}"; 0x0428, "\u{0448}"; + 0x0429, "\u{0449}"; 0x042A, "\u{044A}"; 0x042B, "\u{044B}"; + 0x042C, "\u{044C}"; 0x042D, "\u{044D}"; 0x042E, "\u{044E}"; + 0x042F, "\u{044F}"; 0x0460, "\u{0461}"; 0x0462, "\u{0463}"; + 0x0464, "\u{0465}"; 0x0466, "\u{0467}"; 0x0468, "\u{0469}"; + 0x046A, "\u{046B}"; 0x046C, "\u{046D}"; 0x046E, "\u{046F}"; + 0x0470, "\u{0471}"; 0x0472, "\u{0473}"; 0x0474, "\u{0475}"; + 0x0476, "\u{0477}"; 0x0478, "\u{0479}"; 0x047A, "\u{047B}"; + 0x047C, "\u{047D}"; 0x047E, "\u{047F}"; 0x0480, "\u{0481}"; + 0x048A, "\u{048B}"; 0x048C, "\u{048D}"; 0x048E, "\u{048F}"; + 0x0490, "\u{0491}"; 0x0492, "\u{0493}"; 0x0494, "\u{0495}"; + 0x0496, "\u{0497}"; 0x0498, "\u{0499}"; 0x049A, "\u{049B}"; + 0x049C, "\u{049D}"; 0x049E, "\u{049F}"; 0x04A0, "\u{04A1}"; + 0x04A2, "\u{04A3}"; 0x04A4, "\u{04A5}"; 0x04A6, "\u{04A7}"; + 0x04A8, "\u{04A9}"; 0x04AA, "\u{04AB}"; 0x04AC, "\u{04AD}"; + 0x04AE, "\u{04AF}"; 0x04B0, "\u{04B1}"; 0x04B2, "\u{04B3}"; + 0x04B4, "\u{04B5}"; 0x04B6, "\u{04B7}"; 0x04B8, "\u{04B9}"; + 0x04BA, "\u{04BB}"; 0x04BC, "\u{04BD}"; 0x04BE, "\u{04BF}"; + 0x04C0, "\u{04CF}"; 0x04C1, "\u{04C2}"; 0x04C3, "\u{04C4}"; + 0x04C5, "\u{04C6}"; 0x04C7, "\u{04C8}"; 0x04C9, "\u{04CA}"; + 0x04CB, "\u{04CC}"; 0x04CD, "\u{04CE}"; 0x04D0, "\u{04D1}"; + 0x04D2, "\u{04D3}"; 0x04D4, "\u{04D5}"; 0x04D6, "\u{04D7}"; + 0x04D8, "\u{04D9}"; 0x04DA, "\u{04DB}"; 0x04DC, "\u{04DD}"; + 0x04DE, "\u{04DF}"; 0x04E0, "\u{04E1}"; 0x04E2, "\u{04E3}"; + 0x04E4, "\u{04E5}"; 0x04E6, "\u{04E7}"; 0x04E8, "\u{04E9}"; + 0x04EA, "\u{04EB}"; 0x04EC, "\u{04ED}"; 0x04EE, "\u{04EF}"; + 0x04F0, "\u{04F1}"; 0x04F2, "\u{04F3}"; 0x04F4, "\u{04F5}"; + 0x04F6, "\u{04F7}"; 0x04F8, "\u{04F9}"; 0x04FA, "\u{04FB}"; + 0x04FC, "\u{04FD}"; 0x04FE, "\u{04FF}"; 0x0500, "\u{0501}"; + 0x0502, "\u{0503}"; 0x0504, "\u{0505}"; 0x0506, "\u{0507}"; + 0x0508, "\u{0509}"; 0x050A, "\u{050B}"; 0x050C, "\u{050D}"; + 0x050E, "\u{050F}"; 0x0510, "\u{0511}"; 0x0512, "\u{0513}"; + 0x0514, "\u{0515}"; 0x0516, "\u{0517}"; 0x0518, "\u{0519}"; + 0x051A, "\u{051B}"; 0x051C, "\u{051D}"; 0x051E, "\u{051F}"; + 0x0520, "\u{0521}"; 0x0522, "\u{0523}"; 0x0524, "\u{0525}"; + 0x0526, "\u{0527}"; 0x0528, "\u{0529}"; 0x052A, "\u{052B}"; + 0x052C, "\u{052D}"; 0x052E, "\u{052F}"; 0x0531, "\u{0561}"; + 0x0532, "\u{0562}"; 0x0533, "\u{0563}"; 0x0534, "\u{0564}"; + 0x0535, "\u{0565}"; 0x0536, "\u{0566}"; 0x0537, "\u{0567}"; + 0x0538, "\u{0568}"; 0x0539, "\u{0569}"; 0x053A, "\u{056A}"; + 0x053B, "\u{056B}"; 0x053C, "\u{056C}"; 0x053D, "\u{056D}"; + 0x053E, "\u{056E}"; 0x053F, "\u{056F}"; 0x0540, "\u{0570}"; + 0x0541, "\u{0571}"; 0x0542, "\u{0572}"; 0x0543, "\u{0573}"; + 0x0544, "\u{0574}"; 0x0545, "\u{0575}"; 0x0546, "\u{0576}"; + 0x0547, "\u{0577}"; 0x0548, "\u{0578}"; 0x0549, "\u{0579}"; + 0x054A, "\u{057A}"; 0x054B, "\u{057B}"; 0x054C, "\u{057C}"; + 0x054D, "\u{057D}"; 0x054E, "\u{057E}"; 0x054F, "\u{057F}"; + 0x0550, "\u{0580}"; 0x0551, "\u{0581}"; 0x0552, "\u{0582}"; + 0x0553, "\u{0583}"; 0x0554, "\u{0584}"; 0x0555, "\u{0585}"; + 0x0556, "\u{0586}"; 0x0587, "\u{0565}\u{0582}"; 0x10A0, "\u{2D00}"; + 0x10A1, "\u{2D01}"; 0x10A2, "\u{2D02}"; 0x10A3, "\u{2D03}"; + 0x10A4, "\u{2D04}"; 0x10A5, "\u{2D05}"; 0x10A6, "\u{2D06}"; + 0x10A7, "\u{2D07}"; 0x10A8, "\u{2D08}"; 0x10A9, "\u{2D09}"; + 0x10AA, "\u{2D0A}"; 0x10AB, "\u{2D0B}"; 0x10AC, "\u{2D0C}"; + 0x10AD, "\u{2D0D}"; 0x10AE, "\u{2D0E}"; 0x10AF, "\u{2D0F}"; + 0x10B0, "\u{2D10}"; 0x10B1, "\u{2D11}"; 0x10B2, "\u{2D12}"; + 0x10B3, "\u{2D13}"; 0x10B4, "\u{2D14}"; 0x10B5, "\u{2D15}"; + 0x10B6, "\u{2D16}"; 0x10B7, "\u{2D17}"; 0x10B8, "\u{2D18}"; + 0x10B9, "\u{2D19}"; 0x10BA, "\u{2D1A}"; 0x10BB, "\u{2D1B}"; + 0x10BC, "\u{2D1C}"; 0x10BD, "\u{2D1D}"; 0x10BE, "\u{2D1E}"; + 0x10BF, "\u{2D1F}"; 0x10C0, "\u{2D20}"; 0x10C1, "\u{2D21}"; + 0x10C2, "\u{2D22}"; 0x10C3, "\u{2D23}"; 0x10C4, "\u{2D24}"; + 0x10C5, "\u{2D25}"; 0x10C7, "\u{2D27}"; 0x10CD, "\u{2D2D}"; + 0x13F8, "\u{13F0}"; 0x13F9, "\u{13F1}"; 0x13FA, "\u{13F2}"; + 0x13FB, "\u{13F3}"; 0x13FC, "\u{13F4}"; 0x13FD, "\u{13F5}"; + 0x1C80, "\u{0432}"; 0x1C81, "\u{0434}"; 0x1C82, "\u{043E}"; + 0x1C83, "\u{0441}"; 0x1C84, "\u{0442}"; 0x1C85, "\u{0442}"; + 0x1C86, "\u{044A}"; 0x1C87, "\u{0463}"; 0x1C88, "\u{A64B}"; + 0x1C89, "\u{1C8A}"; 0x1C90, "\u{10D0}"; 0x1C91, "\u{10D1}"; + 0x1C92, "\u{10D2}"; 0x1C93, "\u{10D3}"; 0x1C94, "\u{10D4}"; + 0x1C95, "\u{10D5}"; 0x1C96, "\u{10D6}"; 0x1C97, "\u{10D7}"; + 0x1C98, "\u{10D8}"; 0x1C99, "\u{10D9}"; 0x1C9A, "\u{10DA}"; + 0x1C9B, "\u{10DB}"; 0x1C9C, "\u{10DC}"; 0x1C9D, "\u{10DD}"; + 0x1C9E, "\u{10DE}"; 0x1C9F, "\u{10DF}"; 0x1CA0, "\u{10E0}"; + 0x1CA1, "\u{10E1}"; 0x1CA2, "\u{10E2}"; 0x1CA3, "\u{10E3}"; + 0x1CA4, "\u{10E4}"; 0x1CA5, "\u{10E5}"; 0x1CA6, "\u{10E6}"; + 0x1CA7, "\u{10E7}"; 0x1CA8, "\u{10E8}"; 0x1CA9, "\u{10E9}"; + 0x1CAA, "\u{10EA}"; 0x1CAB, "\u{10EB}"; 0x1CAC, "\u{10EC}"; + 0x1CAD, "\u{10ED}"; 0x1CAE, "\u{10EE}"; 0x1CAF, "\u{10EF}"; + 0x1CB0, "\u{10F0}"; 0x1CB1, "\u{10F1}"; 0x1CB2, "\u{10F2}"; + 0x1CB3, "\u{10F3}"; 0x1CB4, "\u{10F4}"; 0x1CB5, "\u{10F5}"; + 0x1CB6, "\u{10F6}"; 0x1CB7, "\u{10F7}"; 0x1CB8, "\u{10F8}"; + 0x1CB9, "\u{10F9}"; 0x1CBA, "\u{10FA}"; 0x1CBD, "\u{10FD}"; + 0x1CBE, "\u{10FE}"; 0x1CBF, "\u{10FF}"; 0x1E00, "\u{1E01}"; + 0x1E02, "\u{1E03}"; 0x1E04, "\u{1E05}"; 0x1E06, "\u{1E07}"; + 0x1E08, "\u{1E09}"; 0x1E0A, "\u{1E0B}"; 0x1E0C, "\u{1E0D}"; + 0x1E0E, "\u{1E0F}"; 0x1E10, "\u{1E11}"; 0x1E12, "\u{1E13}"; + 0x1E14, "\u{1E15}"; 0x1E16, "\u{1E17}"; 0x1E18, "\u{1E19}"; + 0x1E1A, "\u{1E1B}"; 0x1E1C, "\u{1E1D}"; 0x1E1E, "\u{1E1F}"; + 0x1E20, "\u{1E21}"; 0x1E22, "\u{1E23}"; 0x1E24, "\u{1E25}"; + 0x1E26, "\u{1E27}"; 0x1E28, "\u{1E29}"; 0x1E2A, "\u{1E2B}"; + 0x1E2C, "\u{1E2D}"; 0x1E2E, "\u{1E2F}"; 0x1E30, "\u{1E31}"; + 0x1E32, "\u{1E33}"; 0x1E34, "\u{1E35}"; 0x1E36, "\u{1E37}"; + 0x1E38, "\u{1E39}"; 0x1E3A, "\u{1E3B}"; 0x1E3C, "\u{1E3D}"; + 0x1E3E, "\u{1E3F}"; 0x1E40, "\u{1E41}"; 0x1E42, "\u{1E43}"; + 0x1E44, "\u{1E45}"; 0x1E46, "\u{1E47}"; 0x1E48, "\u{1E49}"; + 0x1E4A, "\u{1E4B}"; 0x1E4C, "\u{1E4D}"; 0x1E4E, "\u{1E4F}"; + 0x1E50, "\u{1E51}"; 0x1E52, "\u{1E53}"; 0x1E54, "\u{1E55}"; + 0x1E56, "\u{1E57}"; 0x1E58, "\u{1E59}"; 0x1E5A, "\u{1E5B}"; + 0x1E5C, "\u{1E5D}"; 0x1E5E, "\u{1E5F}"; 0x1E60, "\u{1E61}"; + 0x1E62, "\u{1E63}"; 0x1E64, "\u{1E65}"; 0x1E66, "\u{1E67}"; + 0x1E68, "\u{1E69}"; 0x1E6A, "\u{1E6B}"; 0x1E6C, "\u{1E6D}"; + 0x1E6E, "\u{1E6F}"; 0x1E70, "\u{1E71}"; 0x1E72, "\u{1E73}"; + 0x1E74, "\u{1E75}"; 0x1E76, "\u{1E77}"; 0x1E78, "\u{1E79}"; + 0x1E7A, "\u{1E7B}"; 0x1E7C, "\u{1E7D}"; 0x1E7E, "\u{1E7F}"; + 0x1E80, "\u{1E81}"; 0x1E82, "\u{1E83}"; 0x1E84, "\u{1E85}"; + 0x1E86, "\u{1E87}"; 0x1E88, "\u{1E89}"; 0x1E8A, "\u{1E8B}"; + 0x1E8C, "\u{1E8D}"; 0x1E8E, "\u{1E8F}"; 0x1E90, "\u{1E91}"; + 0x1E92, "\u{1E93}"; 0x1E94, "\u{1E95}"; 0x1E96, "\u{0068}\u{0331}"; + 0x1E97, "\u{0074}\u{0308}"; 0x1E98, "\u{0077}\u{030A}"; + 0x1E99, "\u{0079}\u{030A}"; 0x1E9A, "\u{0061}\u{02BE}"; + 0x1E9B, "\u{1E61}"; 0x1E9E, "\u{0073}\u{0073}"; 0x1EA0, "\u{1EA1}"; + 0x1EA2, "\u{1EA3}"; 0x1EA4, "\u{1EA5}"; 0x1EA6, "\u{1EA7}"; + 0x1EA8, "\u{1EA9}"; 0x1EAA, "\u{1EAB}"; 0x1EAC, "\u{1EAD}"; + 0x1EAE, "\u{1EAF}"; 0x1EB0, "\u{1EB1}"; 0x1EB2, "\u{1EB3}"; + 0x1EB4, "\u{1EB5}"; 0x1EB6, "\u{1EB7}"; 0x1EB8, "\u{1EB9}"; + 0x1EBA, "\u{1EBB}"; 0x1EBC, "\u{1EBD}"; 0x1EBE, "\u{1EBF}"; + 0x1EC0, "\u{1EC1}"; 0x1EC2, "\u{1EC3}"; 0x1EC4, "\u{1EC5}"; + 0x1EC6, "\u{1EC7}"; 0x1EC8, "\u{1EC9}"; 0x1ECA, "\u{1ECB}"; + 0x1ECC, "\u{1ECD}"; 0x1ECE, "\u{1ECF}"; 0x1ED0, "\u{1ED1}"; + 0x1ED2, "\u{1ED3}"; 0x1ED4, "\u{1ED5}"; 0x1ED6, "\u{1ED7}"; + 0x1ED8, "\u{1ED9}"; 0x1EDA, "\u{1EDB}"; 0x1EDC, "\u{1EDD}"; + 0x1EDE, "\u{1EDF}"; 0x1EE0, "\u{1EE1}"; 0x1EE2, "\u{1EE3}"; + 0x1EE4, "\u{1EE5}"; 0x1EE6, "\u{1EE7}"; 0x1EE8, "\u{1EE9}"; + 0x1EEA, "\u{1EEB}"; 0x1EEC, "\u{1EED}"; 0x1EEE, "\u{1EEF}"; + 0x1EF0, "\u{1EF1}"; 0x1EF2, "\u{1EF3}"; 0x1EF4, "\u{1EF5}"; + 0x1EF6, "\u{1EF7}"; 0x1EF8, "\u{1EF9}"; 0x1EFA, "\u{1EFB}"; + 0x1EFC, "\u{1EFD}"; 0x1EFE, "\u{1EFF}"; 0x1F08, "\u{1F00}"; + 0x1F09, "\u{1F01}"; 0x1F0A, "\u{1F02}"; 0x1F0B, "\u{1F03}"; + 0x1F0C, "\u{1F04}"; 0x1F0D, "\u{1F05}"; 0x1F0E, "\u{1F06}"; + 0x1F0F, "\u{1F07}"; 0x1F18, "\u{1F10}"; 0x1F19, "\u{1F11}"; + 0x1F1A, "\u{1F12}"; 0x1F1B, "\u{1F13}"; 0x1F1C, "\u{1F14}"; + 0x1F1D, "\u{1F15}"; 0x1F28, "\u{1F20}"; 0x1F29, "\u{1F21}"; + 0x1F2A, "\u{1F22}"; 0x1F2B, "\u{1F23}"; 0x1F2C, "\u{1F24}"; + 0x1F2D, "\u{1F25}"; 0x1F2E, "\u{1F26}"; 0x1F2F, "\u{1F27}"; + 0x1F38, "\u{1F30}"; 0x1F39, "\u{1F31}"; 0x1F3A, "\u{1F32}"; + 0x1F3B, "\u{1F33}"; 0x1F3C, "\u{1F34}"; 0x1F3D, "\u{1F35}"; + 0x1F3E, "\u{1F36}"; 0x1F3F, "\u{1F37}"; 0x1F48, "\u{1F40}"; + 0x1F49, "\u{1F41}"; 0x1F4A, "\u{1F42}"; 0x1F4B, "\u{1F43}"; + 0x1F4C, "\u{1F44}"; 0x1F4D, "\u{1F45}"; 0x1F50, "\u{03C5}\u{0313}"; + 0x1F52, "\u{03C5}\u{0313}\u{0300}"; 0x1F54, "\u{03C5}\u{0313}\u{0301}"; + 0x1F56, "\u{03C5}\u{0313}\u{0342}"; 0x1F59, "\u{1F51}"; + 0x1F5B, "\u{1F53}"; 0x1F5D, "\u{1F55}"; 0x1F5F, "\u{1F57}"; + 0x1F68, "\u{1F60}"; 0x1F69, "\u{1F61}"; 0x1F6A, "\u{1F62}"; + 0x1F6B, "\u{1F63}"; 0x1F6C, "\u{1F64}"; 0x1F6D, "\u{1F65}"; + 0x1F6E, "\u{1F66}"; 0x1F6F, "\u{1F67}"; 0x1F80, "\u{1F00}\u{03B9}"; + 0x1F81, "\u{1F01}\u{03B9}"; 0x1F82, "\u{1F02}\u{03B9}"; + 0x1F83, "\u{1F03}\u{03B9}"; 0x1F84, "\u{1F04}\u{03B9}"; + 0x1F85, "\u{1F05}\u{03B9}"; 0x1F86, "\u{1F06}\u{03B9}"; + 0x1F87, "\u{1F07}\u{03B9}"; 0x1F88, "\u{1F00}\u{03B9}"; + 0x1F89, "\u{1F01}\u{03B9}"; 0x1F8A, "\u{1F02}\u{03B9}"; + 0x1F8B, "\u{1F03}\u{03B9}"; 0x1F8C, "\u{1F04}\u{03B9}"; + 0x1F8D, "\u{1F05}\u{03B9}"; 0x1F8E, "\u{1F06}\u{03B9}"; + 0x1F8F, "\u{1F07}\u{03B9}"; 0x1F90, "\u{1F20}\u{03B9}"; + 0x1F91, "\u{1F21}\u{03B9}"; 0x1F92, "\u{1F22}\u{03B9}"; + 0x1F93, "\u{1F23}\u{03B9}"; 0x1F94, "\u{1F24}\u{03B9}"; + 0x1F95, "\u{1F25}\u{03B9}"; 0x1F96, "\u{1F26}\u{03B9}"; + 0x1F97, "\u{1F27}\u{03B9}"; 0x1F98, "\u{1F20}\u{03B9}"; + 0x1F99, "\u{1F21}\u{03B9}"; 0x1F9A, "\u{1F22}\u{03B9}"; + 0x1F9B, "\u{1F23}\u{03B9}"; 0x1F9C, "\u{1F24}\u{03B9}"; + 0x1F9D, "\u{1F25}\u{03B9}"; 0x1F9E, "\u{1F26}\u{03B9}"; + 0x1F9F, "\u{1F27}\u{03B9}"; 0x1FA0, "\u{1F60}\u{03B9}"; + 0x1FA1, "\u{1F61}\u{03B9}"; 0x1FA2, "\u{1F62}\u{03B9}"; + 0x1FA3, "\u{1F63}\u{03B9}"; 0x1FA4, "\u{1F64}\u{03B9}"; + 0x1FA5, "\u{1F65}\u{03B9}"; 0x1FA6, "\u{1F66}\u{03B9}"; + 0x1FA7, "\u{1F67}\u{03B9}"; 0x1FA8, "\u{1F60}\u{03B9}"; + 0x1FA9, "\u{1F61}\u{03B9}"; 0x1FAA, "\u{1F62}\u{03B9}"; + 0x1FAB, "\u{1F63}\u{03B9}"; 0x1FAC, "\u{1F64}\u{03B9}"; + 0x1FAD, "\u{1F65}\u{03B9}"; 0x1FAE, "\u{1F66}\u{03B9}"; + 0x1FAF, "\u{1F67}\u{03B9}"; 0x1FB2, "\u{1F70}\u{03B9}"; + 0x1FB3, "\u{03B1}\u{03B9}"; 0x1FB4, "\u{03AC}\u{03B9}"; + 0x1FB6, "\u{03B1}\u{0342}"; 0x1FB7, "\u{03B1}\u{0342}\u{03B9}"; + 0x1FB8, "\u{1FB0}"; 0x1FB9, "\u{1FB1}"; 0x1FBA, "\u{1F70}"; + 0x1FBB, "\u{1F71}"; 0x1FBC, "\u{03B1}\u{03B9}"; 0x1FBE, "\u{03B9}"; + 0x1FC2, "\u{1F74}\u{03B9}"; 0x1FC3, "\u{03B7}\u{03B9}"; + 0x1FC4, "\u{03AE}\u{03B9}"; 0x1FC6, "\u{03B7}\u{0342}"; + 0x1FC7, "\u{03B7}\u{0342}\u{03B9}"; 0x1FC8, "\u{1F72}"; + 0x1FC9, "\u{1F73}"; 0x1FCA, "\u{1F74}"; 0x1FCB, "\u{1F75}"; + 0x1FCC, "\u{03B7}\u{03B9}"; 0x1FD2, "\u{03B9}\u{0308}\u{0300}"; + 0x1FD3, "\u{03B9}\u{0308}\u{0301}"; 0x1FD6, "\u{03B9}\u{0342}"; + 0x1FD7, "\u{03B9}\u{0308}\u{0342}"; 0x1FD8, "\u{1FD0}"; + 0x1FD9, "\u{1FD1}"; 0x1FDA, "\u{1F76}"; 0x1FDB, "\u{1F77}"; + 0x1FE2, "\u{03C5}\u{0308}\u{0300}"; 0x1FE3, "\u{03C5}\u{0308}\u{0301}"; + 0x1FE4, "\u{03C1}\u{0313}"; 0x1FE6, "\u{03C5}\u{0342}"; + 0x1FE7, "\u{03C5}\u{0308}\u{0342}"; 0x1FE8, "\u{1FE0}"; + 0x1FE9, "\u{1FE1}"; 0x1FEA, "\u{1F7A}"; 0x1FEB, "\u{1F7B}"; + 0x1FEC, "\u{1FE5}"; 0x1FF2, "\u{1F7C}\u{03B9}"; + 0x1FF3, "\u{03C9}\u{03B9}"; 0x1FF4, "\u{03CE}\u{03B9}"; + 0x1FF6, "\u{03C9}\u{0342}"; 0x1FF7, "\u{03C9}\u{0342}\u{03B9}"; + 0x1FF8, "\u{1F78}"; 0x1FF9, "\u{1F79}"; 0x1FFA, "\u{1F7C}"; + 0x1FFB, "\u{1F7D}"; 0x1FFC, "\u{03C9}\u{03B9}"; 0x2126, "\u{03C9}"; + 0x212A, "\u{006B}"; 0x212B, "\u{00E5}"; 0x2132, "\u{214E}"; + 0x2160, "\u{2170}"; 0x2161, "\u{2171}"; 0x2162, "\u{2172}"; + 0x2163, "\u{2173}"; 0x2164, "\u{2174}"; 0x2165, "\u{2175}"; + 0x2166, "\u{2176}"; 0x2167, "\u{2177}"; 0x2168, "\u{2178}"; + 0x2169, "\u{2179}"; 0x216A, "\u{217A}"; 0x216B, "\u{217B}"; + 0x216C, "\u{217C}"; 0x216D, "\u{217D}"; 0x216E, "\u{217E}"; + 0x216F, "\u{217F}"; 0x2183, "\u{2184}"; 0x24B6, "\u{24D0}"; + 0x24B7, "\u{24D1}"; 0x24B8, "\u{24D2}"; 0x24B9, "\u{24D3}"; + 0x24BA, "\u{24D4}"; 0x24BB, "\u{24D5}"; 0x24BC, "\u{24D6}"; + 0x24BD, "\u{24D7}"; 0x24BE, "\u{24D8}"; 0x24BF, "\u{24D9}"; + 0x24C0, "\u{24DA}"; 0x24C1, "\u{24DB}"; 0x24C2, "\u{24DC}"; + 0x24C3, "\u{24DD}"; 0x24C4, "\u{24DE}"; 0x24C5, "\u{24DF}"; + 0x24C6, "\u{24E0}"; 0x24C7, "\u{24E1}"; 0x24C8, "\u{24E2}"; + 0x24C9, "\u{24E3}"; 0x24CA, "\u{24E4}"; 0x24CB, "\u{24E5}"; + 0x24CC, "\u{24E6}"; 0x24CD, "\u{24E7}"; 0x24CE, "\u{24E8}"; + 0x24CF, "\u{24E9}"; 0x2C00, "\u{2C30}"; 0x2C01, "\u{2C31}"; + 0x2C02, "\u{2C32}"; 0x2C03, "\u{2C33}"; 0x2C04, "\u{2C34}"; + 0x2C05, "\u{2C35}"; 0x2C06, "\u{2C36}"; 0x2C07, "\u{2C37}"; + 0x2C08, "\u{2C38}"; 0x2C09, "\u{2C39}"; 0x2C0A, "\u{2C3A}"; + 0x2C0B, "\u{2C3B}"; 0x2C0C, "\u{2C3C}"; 0x2C0D, "\u{2C3D}"; + 0x2C0E, "\u{2C3E}"; 0x2C0F, "\u{2C3F}"; 0x2C10, "\u{2C40}"; + 0x2C11, "\u{2C41}"; 0x2C12, "\u{2C42}"; 0x2C13, "\u{2C43}"; + 0x2C14, "\u{2C44}"; 0x2C15, "\u{2C45}"; 0x2C16, "\u{2C46}"; + 0x2C17, "\u{2C47}"; 0x2C18, "\u{2C48}"; 0x2C19, "\u{2C49}"; + 0x2C1A, "\u{2C4A}"; 0x2C1B, "\u{2C4B}"; 0x2C1C, "\u{2C4C}"; + 0x2C1D, "\u{2C4D}"; 0x2C1E, "\u{2C4E}"; 0x2C1F, "\u{2C4F}"; + 0x2C20, "\u{2C50}"; 0x2C21, "\u{2C51}"; 0x2C22, "\u{2C52}"; + 0x2C23, "\u{2C53}"; 0x2C24, "\u{2C54}"; 0x2C25, "\u{2C55}"; + 0x2C26, "\u{2C56}"; 0x2C27, "\u{2C57}"; 0x2C28, "\u{2C58}"; + 0x2C29, "\u{2C59}"; 0x2C2A, "\u{2C5A}"; 0x2C2B, "\u{2C5B}"; + 0x2C2C, "\u{2C5C}"; 0x2C2D, "\u{2C5D}"; 0x2C2E, "\u{2C5E}"; + 0x2C2F, "\u{2C5F}"; 0x2C60, "\u{2C61}"; 0x2C62, "\u{026B}"; + 0x2C63, "\u{1D7D}"; 0x2C64, "\u{027D}"; 0x2C67, "\u{2C68}"; + 0x2C69, "\u{2C6A}"; 0x2C6B, "\u{2C6C}"; 0x2C6D, "\u{0251}"; + 0x2C6E, "\u{0271}"; 0x2C6F, "\u{0250}"; 0x2C70, "\u{0252}"; + 0x2C72, "\u{2C73}"; 0x2C75, "\u{2C76}"; 0x2C7E, "\u{023F}"; + 0x2C7F, "\u{0240}"; 0x2C80, "\u{2C81}"; 0x2C82, "\u{2C83}"; + 0x2C84, "\u{2C85}"; 0x2C86, "\u{2C87}"; 0x2C88, "\u{2C89}"; + 0x2C8A, "\u{2C8B}"; 0x2C8C, "\u{2C8D}"; 0x2C8E, "\u{2C8F}"; + 0x2C90, "\u{2C91}"; 0x2C92, "\u{2C93}"; 0x2C94, "\u{2C95}"; + 0x2C96, "\u{2C97}"; 0x2C98, "\u{2C99}"; 0x2C9A, "\u{2C9B}"; + 0x2C9C, "\u{2C9D}"; 0x2C9E, "\u{2C9F}"; 0x2CA0, "\u{2CA1}"; + 0x2CA2, "\u{2CA3}"; 0x2CA4, "\u{2CA5}"; 0x2CA6, "\u{2CA7}"; + 0x2CA8, "\u{2CA9}"; 0x2CAA, "\u{2CAB}"; 0x2CAC, "\u{2CAD}"; + 0x2CAE, "\u{2CAF}"; 0x2CB0, "\u{2CB1}"; 0x2CB2, "\u{2CB3}"; + 0x2CB4, "\u{2CB5}"; 0x2CB6, "\u{2CB7}"; 0x2CB8, "\u{2CB9}"; + 0x2CBA, "\u{2CBB}"; 0x2CBC, "\u{2CBD}"; 0x2CBE, "\u{2CBF}"; + 0x2CC0, "\u{2CC1}"; 0x2CC2, "\u{2CC3}"; 0x2CC4, "\u{2CC5}"; + 0x2CC6, "\u{2CC7}"; 0x2CC8, "\u{2CC9}"; 0x2CCA, "\u{2CCB}"; + 0x2CCC, "\u{2CCD}"; 0x2CCE, "\u{2CCF}"; 0x2CD0, "\u{2CD1}"; + 0x2CD2, "\u{2CD3}"; 0x2CD4, "\u{2CD5}"; 0x2CD6, "\u{2CD7}"; + 0x2CD8, "\u{2CD9}"; 0x2CDA, "\u{2CDB}"; 0x2CDC, "\u{2CDD}"; + 0x2CDE, "\u{2CDF}"; 0x2CE0, "\u{2CE1}"; 0x2CE2, "\u{2CE3}"; + 0x2CEB, "\u{2CEC}"; 0x2CED, "\u{2CEE}"; 0x2CF2, "\u{2CF3}"; + 0xA640, "\u{A641}"; 0xA642, "\u{A643}"; 0xA644, "\u{A645}"; + 0xA646, "\u{A647}"; 0xA648, "\u{A649}"; 0xA64A, "\u{A64B}"; + 0xA64C, "\u{A64D}"; 0xA64E, "\u{A64F}"; 0xA650, "\u{A651}"; + 0xA652, "\u{A653}"; 0xA654, "\u{A655}"; 0xA656, "\u{A657}"; + 0xA658, "\u{A659}"; 0xA65A, "\u{A65B}"; 0xA65C, "\u{A65D}"; + 0xA65E, "\u{A65F}"; 0xA660, "\u{A661}"; 0xA662, "\u{A663}"; + 0xA664, "\u{A665}"; 0xA666, "\u{A667}"; 0xA668, "\u{A669}"; + 0xA66A, "\u{A66B}"; 0xA66C, "\u{A66D}"; 0xA680, "\u{A681}"; + 0xA682, "\u{A683}"; 0xA684, "\u{A685}"; 0xA686, "\u{A687}"; + 0xA688, "\u{A689}"; 0xA68A, "\u{A68B}"; 0xA68C, "\u{A68D}"; + 0xA68E, "\u{A68F}"; 0xA690, "\u{A691}"; 0xA692, "\u{A693}"; + 0xA694, "\u{A695}"; 0xA696, "\u{A697}"; 0xA698, "\u{A699}"; + 0xA69A, "\u{A69B}"; 0xA722, "\u{A723}"; 0xA724, "\u{A725}"; + 0xA726, "\u{A727}"; 0xA728, "\u{A729}"; 0xA72A, "\u{A72B}"; + 0xA72C, "\u{A72D}"; 0xA72E, "\u{A72F}"; 0xA732, "\u{A733}"; + 0xA734, "\u{A735}"; 0xA736, "\u{A737}"; 0xA738, "\u{A739}"; + 0xA73A, "\u{A73B}"; 0xA73C, "\u{A73D}"; 0xA73E, "\u{A73F}"; + 0xA740, "\u{A741}"; 0xA742, "\u{A743}"; 0xA744, "\u{A745}"; + 0xA746, "\u{A747}"; 0xA748, "\u{A749}"; 0xA74A, "\u{A74B}"; + 0xA74C, "\u{A74D}"; 0xA74E, "\u{A74F}"; 0xA750, "\u{A751}"; + 0xA752, "\u{A753}"; 0xA754, "\u{A755}"; 0xA756, "\u{A757}"; + 0xA758, "\u{A759}"; 0xA75A, "\u{A75B}"; 0xA75C, "\u{A75D}"; + 0xA75E, "\u{A75F}"; 0xA760, "\u{A761}"; 0xA762, "\u{A763}"; + 0xA764, "\u{A765}"; 0xA766, "\u{A767}"; 0xA768, "\u{A769}"; + 0xA76A, "\u{A76B}"; 0xA76C, "\u{A76D}"; 0xA76E, "\u{A76F}"; + 0xA779, "\u{A77A}"; 0xA77B, "\u{A77C}"; 0xA77D, "\u{1D79}"; + 0xA77E, "\u{A77F}"; 0xA780, "\u{A781}"; 0xA782, "\u{A783}"; + 0xA784, "\u{A785}"; 0xA786, "\u{A787}"; 0xA78B, "\u{A78C}"; + 0xA78D, "\u{0265}"; 0xA790, "\u{A791}"; 0xA792, "\u{A793}"; + 0xA796, "\u{A797}"; 0xA798, "\u{A799}"; 0xA79A, "\u{A79B}"; + 0xA79C, "\u{A79D}"; 0xA79E, "\u{A79F}"; 0xA7A0, "\u{A7A1}"; + 0xA7A2, "\u{A7A3}"; 0xA7A4, "\u{A7A5}"; 0xA7A6, "\u{A7A7}"; + 0xA7A8, "\u{A7A9}"; 0xA7AA, "\u{0266}"; 0xA7AB, "\u{025C}"; + 0xA7AC, "\u{0261}"; 0xA7AD, "\u{026C}"; 0xA7AE, "\u{026A}"; + 0xA7B0, "\u{029E}"; 0xA7B1, "\u{0287}"; 0xA7B2, "\u{029D}"; + 0xA7B3, "\u{AB53}"; 0xA7B4, "\u{A7B5}"; 0xA7B6, "\u{A7B7}"; + 0xA7B8, "\u{A7B9}"; 0xA7BA, "\u{A7BB}"; 0xA7BC, "\u{A7BD}"; + 0xA7BE, "\u{A7BF}"; 0xA7C0, "\u{A7C1}"; 0xA7C2, "\u{A7C3}"; + 0xA7C4, "\u{A794}"; 0xA7C5, "\u{0282}"; 0xA7C6, "\u{1D8E}"; + 0xA7C7, "\u{A7C8}"; 0xA7C9, "\u{A7CA}"; 0xA7CB, "\u{0264}"; + 0xA7CC, "\u{A7CD}"; 0xA7D0, "\u{A7D1}"; 0xA7D6, "\u{A7D7}"; + 0xA7D8, "\u{A7D9}"; 0xA7DA, "\u{A7DB}"; 0xA7DC, "\u{019B}"; + 0xA7F5, "\u{A7F6}"; 0xAB70, "\u{13A0}"; 0xAB71, "\u{13A1}"; + 0xAB72, "\u{13A2}"; 0xAB73, "\u{13A3}"; 0xAB74, "\u{13A4}"; + 0xAB75, "\u{13A5}"; 0xAB76, "\u{13A6}"; 0xAB77, "\u{13A7}"; + 0xAB78, "\u{13A8}"; 0xAB79, "\u{13A9}"; 0xAB7A, "\u{13AA}"; + 0xAB7B, "\u{13AB}"; 0xAB7C, "\u{13AC}"; 0xAB7D, "\u{13AD}"; + 0xAB7E, "\u{13AE}"; 0xAB7F, "\u{13AF}"; 0xAB80, "\u{13B0}"; + 0xAB81, "\u{13B1}"; 0xAB82, "\u{13B2}"; 0xAB83, "\u{13B3}"; + 0xAB84, "\u{13B4}"; 0xAB85, "\u{13B5}"; 0xAB86, "\u{13B6}"; + 0xAB87, "\u{13B7}"; 0xAB88, "\u{13B8}"; 0xAB89, "\u{13B9}"; + 0xAB8A, "\u{13BA}"; 0xAB8B, "\u{13BB}"; 0xAB8C, "\u{13BC}"; + 0xAB8D, "\u{13BD}"; 0xAB8E, "\u{13BE}"; 0xAB8F, "\u{13BF}"; + 0xAB90, "\u{13C0}"; 0xAB91, "\u{13C1}"; 0xAB92, "\u{13C2}"; + 0xAB93, "\u{13C3}"; 0xAB94, "\u{13C4}"; 0xAB95, "\u{13C5}"; + 0xAB96, "\u{13C6}"; 0xAB97, "\u{13C7}"; 0xAB98, "\u{13C8}"; + 0xAB99, "\u{13C9}"; 0xAB9A, "\u{13CA}"; 0xAB9B, "\u{13CB}"; + 0xAB9C, "\u{13CC}"; 0xAB9D, "\u{13CD}"; 0xAB9E, "\u{13CE}"; + 0xAB9F, "\u{13CF}"; 0xABA0, "\u{13D0}"; 0xABA1, "\u{13D1}"; + 0xABA2, "\u{13D2}"; 0xABA3, "\u{13D3}"; 0xABA4, "\u{13D4}"; + 0xABA5, "\u{13D5}"; 0xABA6, "\u{13D6}"; 0xABA7, "\u{13D7}"; + 0xABA8, "\u{13D8}"; 0xABA9, "\u{13D9}"; 0xABAA, "\u{13DA}"; + 0xABAB, "\u{13DB}"; 0xABAC, "\u{13DC}"; 0xABAD, "\u{13DD}"; + 0xABAE, "\u{13DE}"; 0xABAF, "\u{13DF}"; 0xABB0, "\u{13E0}"; + 0xABB1, "\u{13E1}"; 0xABB2, "\u{13E2}"; 0xABB3, "\u{13E3}"; + 0xABB4, "\u{13E4}"; 0xABB5, "\u{13E5}"; 0xABB6, "\u{13E6}"; + 0xABB7, "\u{13E7}"; 0xABB8, "\u{13E8}"; 0xABB9, "\u{13E9}"; + 0xABBA, "\u{13EA}"; 0xABBB, "\u{13EB}"; 0xABBC, "\u{13EC}"; + 0xABBD, "\u{13ED}"; 0xABBE, "\u{13EE}"; 0xABBF, "\u{13EF}"; + 0xFB00, "\u{0066}\u{0066}"; 0xFB01, "\u{0066}\u{0069}"; + 0xFB02, "\u{0066}\u{006C}"; 0xFB03, "\u{0066}\u{0066}\u{0069}"; + 0xFB04, "\u{0066}\u{0066}\u{006C}"; 0xFB05, "\u{0073}\u{0074}"; + 0xFB06, "\u{0073}\u{0074}"; 0xFB13, "\u{0574}\u{0576}"; + 0xFB14, "\u{0574}\u{0565}"; 0xFB15, "\u{0574}\u{056B}"; + 0xFB16, "\u{057E}\u{0576}"; 0xFB17, "\u{0574}\u{056D}"; + 0xFF21, "\u{FF41}"; 0xFF22, "\u{FF42}"; 0xFF23, "\u{FF43}"; + 0xFF24, "\u{FF44}"; 0xFF25, "\u{FF45}"; 0xFF26, "\u{FF46}"; + 0xFF27, "\u{FF47}"; 0xFF28, "\u{FF48}"; 0xFF29, "\u{FF49}"; + 0xFF2A, "\u{FF4A}"; 0xFF2B, "\u{FF4B}"; 0xFF2C, "\u{FF4C}"; + 0xFF2D, "\u{FF4D}"; 0xFF2E, "\u{FF4E}"; 0xFF2F, "\u{FF4F}"; + 0xFF30, "\u{FF50}"; 0xFF31, "\u{FF51}"; 0xFF32, "\u{FF52}"; + 0xFF33, "\u{FF53}"; 0xFF34, "\u{FF54}"; 0xFF35, "\u{FF55}"; + 0xFF36, "\u{FF56}"; 0xFF37, "\u{FF57}"; 0xFF38, "\u{FF58}"; + 0xFF39, "\u{FF59}"; 0xFF3A, "\u{FF5A}"; 0x10400, "\u{10428}"; + 0x10401, "\u{10429}"; 0x10402, "\u{1042A}"; 0x10403, "\u{1042B}"; + 0x10404, "\u{1042C}"; 0x10405, "\u{1042D}"; 0x10406, "\u{1042E}"; + 0x10407, "\u{1042F}"; 0x10408, "\u{10430}"; 0x10409, "\u{10431}"; + 0x1040A, "\u{10432}"; 0x1040B, "\u{10433}"; 0x1040C, "\u{10434}"; + 0x1040D, "\u{10435}"; 0x1040E, "\u{10436}"; 0x1040F, "\u{10437}"; + 0x10410, "\u{10438}"; 0x10411, "\u{10439}"; 0x10412, "\u{1043A}"; + 0x10413, "\u{1043B}"; 0x10414, "\u{1043C}"; 0x10415, "\u{1043D}"; + 0x10416, "\u{1043E}"; 0x10417, "\u{1043F}"; 0x10418, "\u{10440}"; + 0x10419, "\u{10441}"; 0x1041A, "\u{10442}"; 0x1041B, "\u{10443}"; + 0x1041C, "\u{10444}"; 0x1041D, "\u{10445}"; 0x1041E, "\u{10446}"; + 0x1041F, "\u{10447}"; 0x10420, "\u{10448}"; 0x10421, "\u{10449}"; + 0x10422, "\u{1044A}"; 0x10423, "\u{1044B}"; 0x10424, "\u{1044C}"; + 0x10425, "\u{1044D}"; 0x10426, "\u{1044E}"; 0x10427, "\u{1044F}"; + 0x104B0, "\u{104D8}"; 0x104B1, "\u{104D9}"; 0x104B2, "\u{104DA}"; + 0x104B3, "\u{104DB}"; 0x104B4, "\u{104DC}"; 0x104B5, "\u{104DD}"; + 0x104B6, "\u{104DE}"; 0x104B7, "\u{104DF}"; 0x104B8, "\u{104E0}"; + 0x104B9, "\u{104E1}"; 0x104BA, "\u{104E2}"; 0x104BB, "\u{104E3}"; + 0x104BC, "\u{104E4}"; 0x104BD, "\u{104E5}"; 0x104BE, "\u{104E6}"; + 0x104BF, "\u{104E7}"; 0x104C0, "\u{104E8}"; 0x104C1, "\u{104E9}"; + 0x104C2, "\u{104EA}"; 0x104C3, "\u{104EB}"; 0x104C4, "\u{104EC}"; + 0x104C5, "\u{104ED}"; 0x104C6, "\u{104EE}"; 0x104C7, "\u{104EF}"; + 0x104C8, "\u{104F0}"; 0x104C9, "\u{104F1}"; 0x104CA, "\u{104F2}"; + 0x104CB, "\u{104F3}"; 0x104CC, "\u{104F4}"; 0x104CD, "\u{104F5}"; + 0x104CE, "\u{104F6}"; 0x104CF, "\u{104F7}"; 0x104D0, "\u{104F8}"; + 0x104D1, "\u{104F9}"; 0x104D2, "\u{104FA}"; 0x104D3, "\u{104FB}"; + 0x10570, "\u{10597}"; 0x10571, "\u{10598}"; 0x10572, "\u{10599}"; + 0x10573, "\u{1059A}"; 0x10574, "\u{1059B}"; 0x10575, "\u{1059C}"; + 0x10576, "\u{1059D}"; 0x10577, "\u{1059E}"; 0x10578, "\u{1059F}"; + 0x10579, "\u{105A0}"; 0x1057A, "\u{105A1}"; 0x1057C, "\u{105A3}"; + 0x1057D, "\u{105A4}"; 0x1057E, "\u{105A5}"; 0x1057F, "\u{105A6}"; + 0x10580, "\u{105A7}"; 0x10581, "\u{105A8}"; 0x10582, "\u{105A9}"; + 0x10583, "\u{105AA}"; 0x10584, "\u{105AB}"; 0x10585, "\u{105AC}"; + 0x10586, "\u{105AD}"; 0x10587, "\u{105AE}"; 0x10588, "\u{105AF}"; + 0x10589, "\u{105B0}"; 0x1058A, "\u{105B1}"; 0x1058C, "\u{105B3}"; + 0x1058D, "\u{105B4}"; 0x1058E, "\u{105B5}"; 0x1058F, "\u{105B6}"; + 0x10590, "\u{105B7}"; 0x10591, "\u{105B8}"; 0x10592, "\u{105B9}"; + 0x10594, "\u{105BB}"; 0x10595, "\u{105BC}"; 0x10C80, "\u{10CC0}"; + 0x10C81, "\u{10CC1}"; 0x10C82, "\u{10CC2}"; 0x10C83, "\u{10CC3}"; + 0x10C84, "\u{10CC4}"; 0x10C85, "\u{10CC5}"; 0x10C86, "\u{10CC6}"; + 0x10C87, "\u{10CC7}"; 0x10C88, "\u{10CC8}"; 0x10C89, "\u{10CC9}"; + 0x10C8A, "\u{10CCA}"; 0x10C8B, "\u{10CCB}"; 0x10C8C, "\u{10CCC}"; + 0x10C8D, "\u{10CCD}"; 0x10C8E, "\u{10CCE}"; 0x10C8F, "\u{10CCF}"; + 0x10C90, "\u{10CD0}"; 0x10C91, "\u{10CD1}"; 0x10C92, "\u{10CD2}"; + 0x10C93, "\u{10CD3}"; 0x10C94, "\u{10CD4}"; 0x10C95, "\u{10CD5}"; + 0x10C96, "\u{10CD6}"; 0x10C97, "\u{10CD7}"; 0x10C98, "\u{10CD8}"; + 0x10C99, "\u{10CD9}"; 0x10C9A, "\u{10CDA}"; 0x10C9B, "\u{10CDB}"; + 0x10C9C, "\u{10CDC}"; 0x10C9D, "\u{10CDD}"; 0x10C9E, "\u{10CDE}"; + 0x10C9F, "\u{10CDF}"; 0x10CA0, "\u{10CE0}"; 0x10CA1, "\u{10CE1}"; + 0x10CA2, "\u{10CE2}"; 0x10CA3, "\u{10CE3}"; 0x10CA4, "\u{10CE4}"; + 0x10CA5, "\u{10CE5}"; 0x10CA6, "\u{10CE6}"; 0x10CA7, "\u{10CE7}"; + 0x10CA8, "\u{10CE8}"; 0x10CA9, "\u{10CE9}"; 0x10CAA, "\u{10CEA}"; + 0x10CAB, "\u{10CEB}"; 0x10CAC, "\u{10CEC}"; 0x10CAD, "\u{10CED}"; + 0x10CAE, "\u{10CEE}"; 0x10CAF, "\u{10CEF}"; 0x10CB0, "\u{10CF0}"; + 0x10CB1, "\u{10CF1}"; 0x10CB2, "\u{10CF2}"; 0x10D50, "\u{10D70}"; + 0x10D51, "\u{10D71}"; 0x10D52, "\u{10D72}"; 0x10D53, "\u{10D73}"; + 0x10D54, "\u{10D74}"; 0x10D55, "\u{10D75}"; 0x10D56, "\u{10D76}"; + 0x10D57, "\u{10D77}"; 0x10D58, "\u{10D78}"; 0x10D59, "\u{10D79}"; + 0x10D5A, "\u{10D7A}"; 0x10D5B, "\u{10D7B}"; 0x10D5C, "\u{10D7C}"; + 0x10D5D, "\u{10D7D}"; 0x10D5E, "\u{10D7E}"; 0x10D5F, "\u{10D7F}"; + 0x10D60, "\u{10D80}"; 0x10D61, "\u{10D81}"; 0x10D62, "\u{10D82}"; + 0x10D63, "\u{10D83}"; 0x10D64, "\u{10D84}"; 0x10D65, "\u{10D85}"; + 0x118A0, "\u{118C0}"; 0x118A1, "\u{118C1}"; 0x118A2, "\u{118C2}"; + 0x118A3, "\u{118C3}"; 0x118A4, "\u{118C4}"; 0x118A5, "\u{118C5}"; + 0x118A6, "\u{118C6}"; 0x118A7, "\u{118C7}"; 0x118A8, "\u{118C8}"; + 0x118A9, "\u{118C9}"; 0x118AA, "\u{118CA}"; 0x118AB, "\u{118CB}"; + 0x118AC, "\u{118CC}"; 0x118AD, "\u{118CD}"; 0x118AE, "\u{118CE}"; + 0x118AF, "\u{118CF}"; 0x118B0, "\u{118D0}"; 0x118B1, "\u{118D1}"; + 0x118B2, "\u{118D2}"; 0x118B3, "\u{118D3}"; 0x118B4, "\u{118D4}"; + 0x118B5, "\u{118D5}"; 0x118B6, "\u{118D6}"; 0x118B7, "\u{118D7}"; + 0x118B8, "\u{118D8}"; 0x118B9, "\u{118D9}"; 0x118BA, "\u{118DA}"; + 0x118BB, "\u{118DB}"; 0x118BC, "\u{118DC}"; 0x118BD, "\u{118DD}"; + 0x118BE, "\u{118DE}"; 0x118BF, "\u{118DF}"; 0x16E40, "\u{16E60}"; + 0x16E41, "\u{16E61}"; 0x16E42, "\u{16E62}"; 0x16E43, "\u{16E63}"; + 0x16E44, "\u{16E64}"; 0x16E45, "\u{16E65}"; 0x16E46, "\u{16E66}"; + 0x16E47, "\u{16E67}"; 0x16E48, "\u{16E68}"; 0x16E49, "\u{16E69}"; + 0x16E4A, "\u{16E6A}"; 0x16E4B, "\u{16E6B}"; 0x16E4C, "\u{16E6C}"; + 0x16E4D, "\u{16E6D}"; 0x16E4E, "\u{16E6E}"; 0x16E4F, "\u{16E6F}"; + 0x16E50, "\u{16E70}"; 0x16E51, "\u{16E71}"; 0x16E52, "\u{16E72}"; + 0x16E53, "\u{16E73}"; 0x16E54, "\u{16E74}"; 0x16E55, "\u{16E75}"; + 0x16E56, "\u{16E76}"; 0x16E57, "\u{16E77}"; 0x16E58, "\u{16E78}"; + 0x16E59, "\u{16E79}"; 0x16E5A, "\u{16E7A}"; 0x16E5B, "\u{16E7B}"; + 0x16E5C, "\u{16E7C}"; 0x16E5D, "\u{16E7D}"; 0x16E5E, "\u{16E7E}"; + 0x16E5F, "\u{16E7F}"; 0x1E900, "\u{1E922}"; 0x1E901, "\u{1E923}"; + 0x1E902, "\u{1E924}"; 0x1E903, "\u{1E925}"; 0x1E904, "\u{1E926}"; + 0x1E905, "\u{1E927}"; 0x1E906, "\u{1E928}"; 0x1E907, "\u{1E929}"; + 0x1E908, "\u{1E92A}"; 0x1E909, "\u{1E92B}"; 0x1E90A, "\u{1E92C}"; + 0x1E90B, "\u{1E92D}"; 0x1E90C, "\u{1E92E}"; 0x1E90D, "\u{1E92F}"; + 0x1E90E, "\u{1E930}"; 0x1E90F, "\u{1E931}"; 0x1E910, "\u{1E932}"; + 0x1E911, "\u{1E933}"; 0x1E912, "\u{1E934}"; 0x1E913, "\u{1E935}"; + 0x1E914, "\u{1E936}"; 0x1E915, "\u{1E937}"; 0x1E916, "\u{1E938}"; + 0x1E917, "\u{1E939}"; 0x1E918, "\u{1E93A}"; 0x1E919, "\u{1E93B}"; + 0x1E91A, "\u{1E93C}"; 0x1E91B, "\u{1E93D}"; 0x1E91C, "\u{1E93E}"; + 0x1E91D, "\u{1E93F}"; 0x1E91E, "\u{1E940}"; 0x1E91F, "\u{1E941}"; + 0x1E920, "\u{1E942}"; 0x1E921, "\u{1E943}"|] diff --git a/src/markdown2/dune b/src/markdown2/dune index 2836410dcf..5c342ce37c 100644 --- a/src/markdown2/dune +++ b/src/markdown2/dune @@ -1,4 +1,4 @@ (library (name odoc_markdown) (public_name odoc.markdown) - (libraries odoc_model odoc_document cmarkit)) + (libraries odoc_model odoc_document)) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index fd7e28b594..83bb7a24a9 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -6,9 +6,10 @@ module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url module Link = HLink +(* TODO: Remove Md module *) module Md = struct - include Cmarkit - let meta = Cmarkit.Meta.none + include Renderer + let meta = Renderer.Meta.none end let source fn (t : Types.Source.t) = diff --git a/src/markdown2/generator.mli b/src/markdown2/generator.mli index 8ace3211b1..fd26d1013d 100644 --- a/src/markdown2/generator.mli +++ b/src/markdown2/generator.mli @@ -9,10 +9,10 @@ val items : config:Config.t -> resolve:Link.resolve -> Odoc_document.Types.Item.t list -> - Cmarkit.Block.t list + Renderer.Block.t list val inline : config:Config.t -> xref_base_uri:string -> Odoc_document.Types.Inline.t -> - Cmarkit.Inline.t list + Renderer.Inline.t list diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index e227c919e1..ecce36ae87 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -19,17 +19,17 @@ module Url = Odoc_document.Url let make ~config ~url doc children = let filename = Link.Path.as_filename ~config url in let content ppf = - let renderer = Cmarkit_commonmark.renderer () in - Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) + let renderer = Renderer.renderer () in + Format.fprintf ppf "%s" (Renderer.doc_to_string renderer doc) in { Odoc_document.Renderer.filename; content; children; path = url } let make_src ~config ~url _title block_list = let filename = Link.Path.as_filename ~config url in let content (ppf : Format.formatter) = - let renderer = Cmarkit_commonmark.renderer () in - let root_block = Cmarkit.Block.Blocks (block_list, Cmarkit.Meta.none) in - let doc = Cmarkit.Doc.make root_block in - Format.fprintf ppf "%s" (Cmarkit_renderer.doc_to_string renderer doc) + let renderer = Renderer.renderer () in + let root_block = Renderer.Block.Blocks (block_list, Renderer.Meta.none) in + let doc = Renderer.Doc.make root_block in + Format.fprintf ppf "%s" (Renderer.doc_to_string renderer doc) in { Odoc_document.Renderer.filename; content; children = []; path = url } diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index 265dc41ac5..e21b6d9ab5 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -21,7 +21,7 @@ val make : config:Config.t -> url:Odoc_document.Url.Path.t -> - Cmarkit.Doc.t -> + Renderer.Doc.t -> Odoc_document.Renderer.page list -> Odoc_document.Renderer.page @@ -29,5 +29,5 @@ val make_src : config:Config.t -> url:Odoc_document.Url.Path.t -> string -> - Cmarkit.Block.t list -> + Renderer.Block.t list -> Odoc_document.Renderer.page diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml new file mode 100644 index 0000000000..0a819668eb --- /dev/null +++ b/src/markdown2/renderer.ml @@ -0,0 +1,1797 @@ +module Cmarkit_data = struct + module Uset = struct + include Set.Make (Uchar) + let of_array = + let add acc u = add (Uchar.unsafe_of_int u) acc in + Array.fold_left add empty + end + + module Umap = struct + include Map.Make (Uchar) + let of_array = + let add acc (u, f) = add (Uchar.unsafe_of_int u) f acc in + Array.fold_left add empty + end + + let whitespace_uset = Uset.of_array Data_uchar.whitespace + let punctuation_uset = Uset.of_array Data_uchar.punctuation + let case_fold_umap = Umap.of_array Data_uchar.case_fold + + let unicode_version = Data_uchar.unicode_version + let is_unicode_whitespace u = Uset.mem u whitespace_uset + let is_unicode_punctuation u = Uset.mem u punctuation_uset + let unicode_case_fold u = Umap.find_opt u case_fold_umap + + (* HTML entity data. *) + + module String_map = Map.Make (String) +end + +(* TODO: Remove Meta module *) +module Meta = struct + type t = unit + let none = () +end + +(* TODO: Remove Meta.t from node *) +type 'a node = 'a * Meta.t + +module Ascii = struct + let is_control = function '\x00' .. '\x1F' | '\x7F' -> true | _ -> false + let is_letter = function 'a' .. 'z' | 'A' .. 'Z' -> true | _ -> false + let is_upper = function 'A' .. 'Z' -> true | _ -> false + let is_lower = function 'a' .. 'z' -> true | _ -> false + let is_digit = function '0' .. '9' -> true | _ -> false + let is_hex_digit = function + | '0' .. '9' | 'A' .. 'F' | 'a' .. 'f' -> true + | _ -> false + + let hex_digit_to_int = function + | '0' .. '9' as c -> Char.code c - 0x30 + | 'A' .. 'F' as c -> Char.code c - 0x37 + | 'a' .. 'f' as c -> Char.code c - 0x57 + | _ -> assert false + + let is_alphanum = function + | 'a' .. 'z' | 'A' .. 'Z' | '0' .. '9' -> true + | _ -> false + + let is_white = function + | '\x20' | '\x09' | '\x0A' | '\x0B' | '\x0C' | '\x0D' -> true + | _ -> false + + let is_punct = function + (* https://spec.commonmark.org/current/#ascii-punctuation-character *) + | '!' | '\"' | '#' | '$' | '%' | '&' | '\'' | '(' | ')' | '*' | '+' | ',' + | '-' | '.' | '/' | ':' | ';' | '<' | '=' | '>' | '?' | '@' | '[' | '\\' + | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' -> + true + | _ -> false + + let is_blank = function ' ' | '\t' -> true | _ -> false + + let caseless_starts_with ~prefix s = + let get = String.get in + let len_a = String.length prefix in + let len_s = String.length s in + if len_a > len_s then false + else + let max_idx_a = len_a - 1 in + let rec loop s i max = + if i > max then true + else + let c = + match get s i with + | 'A' .. 'Z' as c -> Char.(unsafe_chr (code c + 32)) + | c -> c + in + if get prefix i <> c then false else loop s (i + 1) max + in + loop s 0 max_idx_a + + let match' ~sub s ~start = + (* assert (start + String.length sub - 1 < String.length s) *) + try + for i = 0 to String.length sub - 1 do + if s.[start + i] <> sub.[i] then raise_notrace Exit + done; + true + with Exit -> false + + let caseless_match ~sub s ~start = + (* assert (start + String.length sub - 1 < String.length s) *) + try + for i = 0 to String.length sub - 1 do + let c = + match s.[start + i] with + | 'A' .. 'Z' as c -> Char.(unsafe_chr (code c + 32)) + | c -> c + in + if c <> sub.[i] then raise_notrace Exit + done; + true + with Exit -> false + + let lowercase_sub s first len = + let b = Bytes.create len in + for i = 0 to len - 1 do + let c = + match s.[first + i] with + | 'A' .. 'Z' as c -> Char.(unsafe_chr (code c + 32)) + | c -> c + in + Bytes.set b i c + done; + Bytes.unsafe_to_string b +end + +module Match = struct + let rec first_non_blank s ~last ~start = + if start > last then last + 1 + else + match s.[start] with + | ' ' | '\t' -> first_non_blank s ~last ~start:(start + 1) + | _ -> start + + let autolink_email s ~last ~start = + (* https://spec.commonmark.org/current/#email-address + Via the ABNF "<" email ">" with email defined by: + https://html.spec.whatwg.org/multipage/input.html#valid-e-mail-address *) + let is_atext_plus_dot = function + | 'a' .. 'z' + | 'A' .. 'Z' + | '0' .. '9' + | '!' | '#' | '$' | '%' | '&' | '\'' | '*' | '+' | '-' | '/' | '=' | '?' + | '^' | '_' | '`' | '{' | '|' | '}' | '~' | '.' -> + true + | _ -> false + in + let is_let_dig = Ascii.is_alphanum in + let is_let_dig_hyp c = Ascii.is_alphanum c || c = '-' in + let rec label_seq s last k = + let rec loop s last c k = + if k > last then None + else if is_let_dig_hyp s.[k] && c <= 63 then loop s last (c + 1) (k + 1) + else if c > 63 || not (is_let_dig s.[k - 1]) then None + else + match s.[k] with + | '>' -> Some k + | '.' -> label_seq s last (k + 1) + | _ -> None + in + if k > last || not (is_let_dig s.[k]) then None else loop s last 1 (k + 1) + in + let rec atext_seq s last k = + if k > last then None + else if is_atext_plus_dot s.[k] then atext_seq s last (k + 1) + else if s.[k] = '@' && is_atext_plus_dot s.[k - 1] then + label_seq s last (k + 1) + else None + in + if start > last || s.[start] <> '<' then None + else atext_seq s last (start + 1) +end + +module Layout = struct + type blanks = string + type nonrec string = string + type nonrec char = char + type count = int + type indent = int + let string ?(meta = Meta.none) s = (s, meta) + let empty = string "" +end + +module Block_line = struct + let _list_of_string flush s = + (* cuts [s] on newlines *) + let rec loop s acc max start k = + if k > max then List.rev (flush s start max acc) + else if not (s.[k] = '\n' || s.[k] = '\r') then + loop s acc max start (k + 1) + else + let acc = flush s start (k - 1) acc in + let next = k + 1 in + let start = + if s.[k] = '\r' && next <= max && s.[next] = '\n' then next + 1 + else next + in + loop s acc max start start + in + loop s [] (String.length s - 1) 0 0 + + let flush ?(meta = Meta.none) s start last acc = + let sub = String.sub s start (last - start + 1) in + (sub, meta) :: acc + + let flush_tight ?(meta = Meta.none) s start last acc = + (* If [s] has newlines, blanks after newlines are layout *) + if start > last then ("", ("", meta)) :: acc + else + match acc with + | [] (* On the first line the blanks are legit *) -> + ("", (String.sub s start (last - start + 1), meta)) :: acc + | acc -> + let nb = Match.first_non_blank s ~last ~start in + ( String.sub s start (nb - 1 - start + 1), + (String.sub s nb (last - nb + 1), meta) ) + :: acc + + (* Block lines *) + + type t = string node + + let to_string = fst + let list_of_string ?meta s = _list_of_string (flush ?meta) s + + (* Tight lines *) + + type tight = Layout.blanks * t + + let tight_to_string l = fst (snd l) + let tight_list_of_string ?meta s = _list_of_string (flush_tight ?meta) s + + (* Blank lines *) + + type blank = Layout.blanks node +end + +module Label = struct + type key = string + type t = { meta : Meta.t; key : key; text : Block_line.tight list } + let make ?(meta = Meta.none) ~key text = { key; text; meta } + let with_meta meta l = { l with meta } + let meta t = t.meta + let key t = t.key + let text t = t.text + let text_to_string t = + String.concat " " (List.map Block_line.tight_to_string t.text) + + let compare l0 l1 = String.compare l0.key l1.key + + (* Definitions *) + + module Map = Map.Make (String) + type def = .. + type defs = def Map.t + + (* Resolvers *) + + type context = + [ `Def of t option * t | `Ref of [ `Link | `Image ] * t * t option ] + + type resolver = context -> t option + let default_resolver = function + | `Def (None, k) -> Some k + | `Def (Some _, _k) -> None + | `Ref (_, _, k) -> k +end + +module Link_definition = struct + type layout = { + indent : Layout.indent; + angled_dest : bool; + before_dest : Block_line.blank list; + after_dest : Block_line.blank list; + title_open_delim : Layout.char; + after_title : Block_line.blank list; + } + + let layout_for_dest dest = + let needs_angles c = Ascii.is_control c || c = ' ' in + let angled_dest = String.exists needs_angles dest in + { + indent = 0; + angled_dest; + before_dest = []; + after_dest = []; + title_open_delim = '\"'; + after_title = []; + } + + let default_layout = + { + indent = 0; + angled_dest = false; + before_dest = []; + after_dest = []; + title_open_delim = '\"'; + after_title = []; + } + + type t = { + layout : layout; + label : Label.t option; + defined_label : Label.t option; + dest : string node option; + title : Block_line.tight list option; + } + + let make ?defined_label ?label ?dest ?title () = + let layout = + match dest with + | None -> default_layout + | Some (d, _) -> layout_for_dest d + in + let defined_label = + match defined_label with None -> label | Some d -> d + in + { layout; label; defined_label; dest; title } + + let layout ld = ld.layout + let label ld = ld.label + let defined_label ld = ld.defined_label + let dest ld = ld.dest + let title ld = ld.title + + type Label.def += Def of t node +end + +module Inline = struct + type t = .. + + module Autolink = struct + type t = { is_email : bool; link : string node } + let is_email a = a.is_email + let link a = a.link + let make link = + let is_email = + let l = String.concat "" [ "<"; fst link; ">" ] in + match Match.autolink_email l ~last:(String.length l - 1) ~start:0 with + | None -> false + | Some _ -> true + in + { is_email; link } + end + + module Break = struct + type type' = [ `Hard | `Soft ] + type t = { + layout_before : Layout.blanks node; + type' : type'; + layout_after : Layout.blanks node; + } + + let make ?(layout_before = Layout.empty) ?(layout_after = Layout.empty) + type' = + { layout_before; type'; layout_after } + + let type' b = b.type' + let layout_before b = b.layout_before + let layout_after b = b.layout_after + end + + module Code_span = struct + type t = { + backtick_count : Layout.count; + code_layout : Block_line.tight list; + } + + let make ~backtick_count code_layout = { backtick_count; code_layout } + + let min_backtick_count ~min counts = + let rec loop min = function + | c :: cs -> if min <> c then min else loop (c + 1) cs + | [] -> min + in + loop min (List.sort Int.compare counts) + + let of_string ?(meta = Meta.none) = function + | "" -> { backtick_count = 1; code_layout = [ ("", ("", meta)) ] } + | s -> + (* This finds out the needed backtick count, whether spaces are needed, + and treats blanks after newline as layout *) + let max = String.length s - 1 in + let need_sp = s.[0] = '`' || s.[max] = '`' in + let s = if need_sp then String.concat "" [ " "; s; " " ] else s in + let backtick_counts, code_layout = + let rec loop bt_counts acc max btc start k = + match k > max with + | true -> + (* assert (btc = 0) because of [need_sp] *) + ( bt_counts, + if acc = [] then [ ("", (s, meta)) ] + else List.rev (Block_line.flush_tight ~meta s start max acc) + ) + | false -> + if s.[k] = '`' then + loop bt_counts acc max (btc + 1) start (k + 1) + else + let bt_counts = + if btc > 0 then btc :: bt_counts else bt_counts + in + if not (s.[k] = '\n' || s.[k] = '\r') then + loop bt_counts acc max 0 start (k + 1) + else + let acc = + Block_line.flush_tight ~meta s start (k - 1) acc + in + let start = + if k + 1 <= max && s.[k] = '\r' && s.[k + 1] = '\n' then + k + 2 + else k + 1 + in + loop bt_counts acc max 0 start start + in + loop [] [] max 0 0 0 + in + let backtick_count = min_backtick_count ~min:1 backtick_counts in + { backtick_count; code_layout } + + let backtick_count cs = cs.backtick_count + let code_layout cs = cs.code_layout + let code cs = + (* Extract code, see https://spec.commonmark.org/0.30/#code-spans *) + let sp c = Char.equal c ' ' in + let s = List.map Block_line.tight_to_string cs.code_layout in + let s = String.concat " " s in + if s = "" then "" + else if + s.[0] = ' ' + && s.[String.length s - 1] = ' ' + && not (String.for_all sp s) + then String.sub s 1 (String.length s - 2) + else s + end + + module Emphasis = struct + type inline = t + type t = { delim : Layout.char; inline : inline } + let make ?(delim = '*') inline = { delim; inline } + let inline e = e.inline + let delim e = e.delim + end + + module Link = struct + type inline = t + + type reference_layout = [ `Collapsed | `Full | `Shortcut ] + type reference = + [ `Inline of Link_definition.t node + | `Ref of reference_layout * Label.t * Label.t ] + + type t = { text : inline; reference : reference } + + let make text reference = { text; reference } + let text l = l.text + let reference l = l.reference + let referenced_label l = + match l.reference with `Inline _ -> None | `Ref (_, _, k) -> Some k + + let reference_definition defs l = + match l.reference with + | `Inline ld -> Some (Link_definition.Def ld) + | `Ref (_, _, def) -> Label.Map.find_opt (Label.key def) defs + + let is_unsafe l = + let allowed_data_url l = + let allowed = + [ "image/gif"; "image/png"; "image/jpeg"; "image/webp" ] + in + (* Extract mediatype from data:[][;base64], *) + match String.index_from_opt l 4 ',' with + | None -> false + | Some j -> + let k = + match String.index_from_opt l 4 ';' with None -> j | Some k -> k + in + let t = String.sub l 5 (min j k - 5) in + List.mem t allowed + in + Ascii.caseless_starts_with ~prefix:"javascript:" l + || Ascii.caseless_starts_with ~prefix:"vbscript:" l + || Ascii.caseless_starts_with ~prefix:"file:" l + || Ascii.caseless_starts_with ~prefix:"data:" l + && not (allowed_data_url l) + end + + module Raw_html = struct + type t = Block_line.tight list + end + + module Text = struct + type t = string + end + + type t += + | Autolink of Autolink.t node + | Break of Break.t node + | Code_span of Code_span.t node + | Emphasis of Emphasis.t node + | Image of Link.t node + | Inlines of t list node + | Link of Link.t node + | Raw_html of Raw_html.t node + | Strong_emphasis of Emphasis.t node + | Text of Text.t node + + let empty = Inlines ([], Meta.none) + + let err_unknown = "Unknown Cmarkit.Inline.t type extension" + + (* Extensions *) + + module Strikethrough = struct + type nonrec t = t + let make = Fun.id + let inline = Fun.id + end + + module Math_span = struct + type t = { display : bool; tex_layout : Block_line.tight list } + let make ~display tex_layout = { display; tex_layout } + let display ms = ms.display + let tex_layout ms = ms.tex_layout + let tex ms = + let s = List.map Block_line.tight_to_string ms.tex_layout in + String.concat " " s + end + + type t += + | Ext_strikethrough of Strikethrough.t node + | Ext_math_span of Math_span.t node + + (* Functions on inlines *) + + let is_empty = function Text ("", _) | Inlines ([], _) -> true | _ -> false + + let ext_none _ = invalid_arg err_unknown + let meta ?(ext = ext_none) = function + | Autolink (_, m) + | Break (_, m) + | Code_span (_, m) + | Emphasis (_, m) + | Image (_, m) + | Inlines (_, m) + | Link (_, m) + | Raw_html (_, m) + | Strong_emphasis (_, m) + | Text (_, m) -> + m + | Ext_strikethrough (_, m) -> m + | Ext_math_span (_, m) -> m + | i -> ext i + + let rec normalize ?(ext = ext_none) = function + | ( Autolink _ | Break _ | Code_span _ | Raw_html _ | Text _ + | Inlines ([], _) + | Ext_math_span _ ) as i -> + i + | Image (l, m) -> Image ({ l with text = normalize ~ext l.text }, m) + | Link (l, m) -> Link ({ l with text = normalize ~ext l.text }, m) + | Inlines ([ i ], _) -> i + | Emphasis (e, m) -> + Emphasis ({ e with inline = normalize ~ext e.inline }, m) + | Strong_emphasis (e, m) -> + Strong_emphasis ({ e with inline = normalize ~ext e.inline }, m) + | Inlines (i :: is, m) -> ( + let rec loop acc = function + | Inlines (is', _) :: is -> + loop acc (List.rev_append (List.rev is') is) + | (Text (t', _) as i') :: is -> ( + match acc with + | Text (t, _) :: acc -> + let i = Text (t ^ t', ()) in + loop (i :: acc) is + | _ -> loop (normalize ~ext i' :: acc) is) + | i :: is -> loop (normalize ~ext i :: acc) is + | [] -> List.rev acc + in + let is = loop [ normalize ~ext i ] is in + match is with [ i ] -> i | _ -> Inlines (is, m)) + | Ext_strikethrough (i, m) -> Ext_strikethrough (normalize ~ext i, m) + | i -> ext i + + let ext_none = ext_none + let to_plain_text ?(ext = ext_none) ~break_on_soft i = + let push s acc = (s :: List.hd acc) :: List.tl acc in + let newline acc = [] :: List.rev (List.hd acc) :: List.tl acc in + let rec loop ~break_on_soft acc = function + | Autolink (a, _) :: is -> + let acc = push (String.concat "" [ "<"; fst a.link; ">" ]) acc in + loop ~break_on_soft acc is + | Break ({ type' = `Hard; _ }, _) :: is -> + loop ~break_on_soft (newline acc) is + | Break ({ type' = `Soft; _ }, _) :: is -> + let acc = if break_on_soft then newline acc else push " " acc in + loop ~break_on_soft acc is + | Code_span (cs, _) :: is -> + loop ~break_on_soft (push (Code_span.code cs) acc) is + | Emphasis ({ inline; _ }, _) :: is + | Strong_emphasis ({ inline; _ }, _) :: is -> + loop ~break_on_soft acc (inline :: is) + | Inlines (is', _) :: is -> + loop ~break_on_soft acc (List.rev_append (List.rev is') is) + | Link (l, _) :: is | Image (l, _) :: is -> + loop ~break_on_soft acc (l.text :: is) + | Raw_html _ :: is -> loop ~break_on_soft acc is + | Text (t, _) :: is -> loop ~break_on_soft (push t acc) is + | Ext_strikethrough (i, _) :: is -> loop ~break_on_soft acc (i :: is) + | Ext_math_span (m, _) :: is -> + loop ~break_on_soft (push (Math_span.tex m) acc) is + | i :: is -> loop ~break_on_soft acc (ext ~break_on_soft i :: is) + | [] -> List.rev (List.rev (List.hd acc) :: List.tl acc) + in + loop ~break_on_soft ([] :: []) [ i ] + + let id ?buf ?ext i = + let text = to_plain_text ?ext ~break_on_soft:false i in + let s = String.concat "\n" (List.map (String.concat "") text) in + let b = + match buf with + | Some b -> + Buffer.reset b; + b + | None -> Buffer.create 256 + in + let[@inline] collapse_blanks b ~prev_byte = + (* Collapses non initial white *) + if Ascii.is_blank prev_byte && Buffer.length b <> 0 then + Buffer.add_char b '-' + in + let rec loop b s max ~prev_byte k = + if k > max then Buffer.contents b + else + match s.[k] with + | (' ' | '\t') as prev_byte -> loop b s max ~prev_byte (k + 1) + | ('_' | '-') as c -> + collapse_blanks b ~prev_byte; + Buffer.add_char b c; + loop b s max ~prev_byte:c (k + 1) + | _ -> + let () = collapse_blanks b ~prev_byte in + let d = String.get_utf_8_uchar s k in + let u = Uchar.utf_decode_uchar d in + let u = match Uchar.to_int u with 0x0000 -> Uchar.rep | _ -> u in + let k' = k + Uchar.utf_decode_length d in + if Cmarkit_data.is_unicode_punctuation u then + loop b s max ~prev_byte:'\x00' k' + else + let () = + match Cmarkit_data.unicode_case_fold u with + | None -> Buffer.add_utf_8_uchar b u + | Some fold -> Buffer.add_string b fold + in + let prev_byte = s.[k] in + loop b s max ~prev_byte k' + in + loop b s (String.length s - 1) ~prev_byte:'\x00' 0 +end + +module Block = struct + type t = .. + + module Blank_line = struct + type t = Layout.blanks + end + + module Block_quote = struct + type nonrec t = { indent : Layout.indent; block : t } + let make ?(indent = 0) block = { indent; block } + let indent bq = bq.indent + let block bq = bq.block + end + + module Code_block = struct + type fenced_layout = { + indent : Layout.indent; + opening_fence : Layout.string node; + closing_fence : Layout.string node option; + } + + let default_fenced_layout = + { + indent = 0; + opening_fence = Layout.empty; + closing_fence = Some Layout.empty; + } + + type layout = [ `Indented | `Fenced of fenced_layout ] + type t = { + layout : layout; + info_string : string node option; + code : string node list; + } + + let make ?(layout = `Fenced default_fenced_layout) ?info_string code = + let layout = + match (info_string, layout) with + | Some _, `Indented -> `Fenced default_fenced_layout + | _, layout -> layout + in + { layout; info_string; code } + + let layout cb = cb.layout + let info_string cb = cb.info_string + let code cb = cb.code + + let make_fence cb = + let rec loop char counts = function + | [] -> counts + | (c, _) :: cs -> + let max = String.length c - 1 in + let k = ref 0 in + while !k <= max && c.[!k] = char do + incr k + done; + loop char (if !k <> 0 then !k :: counts else counts) cs + in + let char = + match cb.info_string with + | Some (i, _) when String.exists (Char.equal '`') i -> '~' + | None | Some _ -> '`' + in + let counts = loop char [] cb.code in + ( char, + Inline.Code_span.min_backtick_count (* not char specific *) + ~min:3 counts ) + + let language_of_info_string s = + let rec next_white s max i = + if i > max || Ascii.is_white s.[i] then i else next_white s max (i + 1) + in + if s = "" then None + else + let max = String.length s - 1 in + let white = next_white s max 0 in + let rem_first = Match.first_non_blank s ~last:max ~start:white in + let lang = String.sub s 0 white in + if lang = "" then None + else Some (lang, String.sub s rem_first (max - rem_first + 1)) + + let is_math_block = function + | None -> false + | Some (i, _) -> ( + match language_of_info_string i with + | Some ("math", _) -> true + | Some _ | None -> false) + end + + module Heading = struct + type atx_layout = { + indent : Layout.indent; + after_opening : Layout.blanks; + closing : Layout.string; + } + + let default_atx_layout = { indent = 0; after_opening = ""; closing = "" } + + type setext_layout = { + leading_indent : Layout.indent; + trailing_blanks : Layout.blanks; + underline_indent : Layout.indent; + underline_count : Layout.count node; + underline_blanks : Layout.blanks; + } + + type layout = [ `Atx of atx_layout | `Setext of setext_layout ] + type id = [ `Auto of string | `Id of string ] + type t = { layout : layout; level : int; inline : Inline.t; id : id option } + + let make ?id ?(layout = `Atx default_atx_layout) ~level inline = + let max = match layout with `Atx _ -> 6 | `Setext _ -> 2 in + let level = Int.max 1 (Int.min level max) in + { layout; level; inline; id } + + let layout h = h.layout + let level h = h.level + let inline h = h.inline + let id h = h.id + end + + module Html_block = struct + type t = string node list + end + + module List_item = struct + type block = t + type t = { + before_marker : Layout.indent; + marker : Layout.string node; + after_marker : Layout.indent; + block : block; + ext_task_marker : Uchar.t node option; + } + + let make ?(before_marker = 0) ?(marker = Layout.empty) ?(after_marker = 1) + ?ext_task_marker block = + { before_marker; marker; after_marker; block; ext_task_marker } + + let block i = i.block + let before_marker i = i.before_marker + let marker i = i.marker + let after_marker i = i.after_marker + let ext_task_marker i = i.ext_task_marker + let task_status_of_task_marker u = + match Uchar.to_int u with + | 0x0020 -> `Unchecked + | 0x0078 (* x *) + | 0x0058 (* X *) + | 0x2713 (* ✓ *) + | 0x2714 (* ✔ *) + | 0x10102 (* 𐄂 *) + | 0x1F5F8 (* 🗸*) -> + `Checked + | 0x007E (* ~ *) -> `Cancelled + | _ -> `Other u + end + + module List' = struct + type type' = [ `Unordered of Layout.char | `Ordered of int * Layout.char ] + type t = { type' : type'; tight : bool; items : List_item.t node list } + + let make ?(tight = true) type' items = { type'; tight; items } + + let type' l = l.type' + let tight l = l.tight + let items l = l.items + end + + module Paragraph = struct + type t = { + leading_indent : Layout.indent; + inline : Inline.t; + trailing_blanks : Layout.blanks; + } + + let make ?(leading_indent = 0) ?(trailing_blanks = "") inline = + { leading_indent; inline; trailing_blanks } + + let inline p = p.inline + let leading_indent p = p.leading_indent + let trailing_blanks p = p.trailing_blanks + end + + module Thematic_break = struct + type t = { indent : Layout.indent; layout : Layout.string } + let make ?(indent = 0) ?(layout = "---") () = { indent; layout } + let indent t = t.indent + let layout t = t.layout + end + + type t += + | Blank_line of Layout.blanks node + | Block_quote of Block_quote.t node + | Blocks of t list node + | Code_block of Code_block.t node + | Heading of Heading.t node + | Html_block of Html_block.t node + | Link_reference_definition of Link_definition.t node + | List of List'.t node + | Paragraph of Paragraph.t node + | Thematic_break of Thematic_break.t node + + let empty = Blocks ([], Meta.none) + + (* Extensions *) + + module Table = struct + type align = [ `Left | `Center | `Right ] + type sep = align option * Layout.count + type cell_layout = Layout.blanks * Layout.blanks + type row = + [ `Header of (Inline.t * cell_layout) list + | `Sep of sep node list + | `Data of (Inline.t * cell_layout) list ] + + type t = { + indent : Layout.indent; + col_count : int; + rows : (row node * Layout.blanks) list; + } + + let col_count rows = + let rec loop c = function + | (((`Header cols | `Data cols), _), _) :: rs -> + loop (Int.max (List.length cols) c) rs + | ((`Sep cols, _), _) :: rs -> loop (Int.max (List.length cols) c) rs + | [] -> c + in + loop 0 rows + + let make ?(indent = 0) rows = { indent; col_count = col_count rows; rows } + let indent t = t.indent + let col_count t = t.col_count + let rows t = t.rows + + let parse_sep_row cs = + let rec loop acc = function + | [] -> Some (List.rev acc) + | (Inline.Text (s, meta), ("", "")) :: cs -> ( + if s = "" then None + else + let max = String.length s - 1 in + let first_colon = s.[0] = ':' and last_colon = s.[max] = ':' in + let first = if first_colon then 1 else 0 in + let last = if last_colon then max - 1 else max in + match + for i = first to last do + if s.[i] <> '-' then raise Exit + done + with + | exception Exit -> None + | () -> + let count = last - first + 1 in + let sep = + match (first_colon, last_colon) with + | false, false -> None + | true, true -> Some `Center + | true, false -> Some `Left + | false, true -> Some `Right + in + loop (((sep, count), meta) :: acc) cs) + | _ -> None + in + loop [] cs + end + + module Footnote = struct + type nonrec t = { + indent : Layout.indent; + label : Label.t; + defined_label : Label.t option; + block : t; + } + + let make ?(indent = 0) ?defined_label:d label block = + let defined_label = match d with None -> Some label | Some d -> d in + { indent; label; defined_label; block } + + let indent fn = fn.indent + let label fn = fn.label + let defined_label fn = fn.defined_label + let block fn = fn.block + + type Label.def += Def of t node + let stub label defined_label = + Def ({ indent = 0; label; defined_label; block = empty }, Meta.none) + end + + type t += + | Ext_math_block of Code_block.t node + | Ext_table of Table.t node + | Ext_footnote_definition of Footnote.t node + + (* Functions on blocks *) + + let err_unknown = "Unknown Cmarkit.Block.t type extension" + + let ext_none _ = invalid_arg err_unknown + let meta ?(ext = ext_none) = function + | Blank_line (_, m) + | Block_quote (_, m) + | Blocks (_, m) + | Code_block (_, m) + | Heading (_, m) + | Html_block (_, m) + | Link_reference_definition (_, m) + | List (_, m) + | Paragraph (_, m) + | Thematic_break (_, m) + | Ext_math_block (_, m) + | Ext_table (_, m) + | Ext_footnote_definition (_, m) -> + m + | b -> ext b + + let rec normalize ?(ext = ext_none) = function + | ( Blank_line _ | Code_block _ | Heading _ | Html_block _ + | Link_reference_definition _ | Paragraph _ | Thematic_break _ + | Blocks ([], _) + | Ext_math_block _ | Ext_table _ ) as b -> + b + | Block_quote (b, m) -> + let b = { b with block = normalize ~ext b.block } in + Block_quote (b, m) + | List (l, m) -> + let item (i, meta) = + let block = List_item.block i in + ({ i with List_item.block = normalize ~ext block }, meta) + in + List ({ l with items = List.map item l.items }, m) + | Blocks (b :: bs, m) -> ( + let rec loop acc = function + | Blocks (bs', _) :: bs -> + loop acc (List.rev_append (List.rev bs') bs) + | b :: bs -> loop (normalize ~ext b :: acc) bs + | [] -> List.rev acc + in + let bs = loop [ normalize ~ext b ] bs in + match bs with [ b ] -> b | _ -> Blocks (bs, m)) + | Ext_footnote_definition (fn, m) -> + let fn = { fn with block = normalize ~ext fn.block } in + Ext_footnote_definition (fn, m) + | b -> ext b + + let rec defs ?(ext = fun _b _defs -> invalid_arg err_unknown) + ?(init = Label.Map.empty) = function + | Blank_line _ | Code_block _ | Heading _ | Html_block _ | Paragraph _ + | Thematic_break _ | Ext_math_block _ | Ext_table _ -> + init + | Block_quote (b, _) -> defs ~ext ~init (Block_quote.block b) + | Blocks (bs, _) -> List.fold_left (fun init b -> defs ~ext ~init b) init bs + | List (l, _) -> + let add init (i, _) = defs ~ext ~init (List_item.block i) in + List.fold_left add init l.items + | Link_reference_definition ld -> ( + match Link_definition.defined_label (fst ld) with + | None -> init + | Some def -> + Label.Map.add (Label.key def) (Link_definition.Def ld) init) + | Ext_footnote_definition fn -> + let init = + match Footnote.defined_label (fst fn) with + | None -> init + | Some def -> Label.Map.add (Label.key def) (Footnote.Def fn) init + in + defs ~ext ~init (Footnote.block (fst fn)) + | b -> ext init b +end + +module Doc = struct + type t = { nl : Layout.string; block : Block.t; defs : Label.defs } + let make ?(nl = "\n") ?(defs = Label.Map.empty) block = { nl; block; defs } + let empty = make (Block.Blocks ([], Meta.none)) + let nl d = d.nl + let block d = d.block + let defs d = d.defs + let unicode_version = Data_uchar.unicode_version + let commonmark_version = "0.30" +end + +(* Heterogeneous dictionaries *) + +module Dict = struct + (* Type identifiers, can be deleted once we require 5.1 *) + module Type = struct + type (_, _) eq = Equal : ('a, 'a) eq + module Id = struct + type _ id = .. + module type ID = sig + type t + type _ id += Id : t id + end + type 'a t = (module ID with type t = 'a) + + let make (type a) () : a t = + (module struct + type t = a + type _ id += Id : t id + end) + + let provably_equal (type a b) ((module A) : a t) ((module B) : b t) : + (a, b) eq option = + match A.Id with B.Id -> Some Equal | _ -> None + + let uid (type a) ((module A) : a t) = + Obj.Extension_constructor.id (Obj.Extension_constructor.of_val A.Id) + end + end + + module M = Map.Make (Int) + type 'a key = 'a Type.Id.t + type binding = B : 'a key * 'a -> binding + type t = binding M.t + + let key = Type.Id.make + let empty = M.empty + let mem k m = M.mem (Type.Id.uid k) m + let add k v m = M.add (Type.Id.uid k) (B (k, v)) m + let tag k m = add k () m + let remove k m = M.remove (Type.Id.uid k) m + let find : type a. a key -> t -> a option = + fun k m -> + match M.find_opt (Type.Id.uid k) m with + | None -> None + | Some (B (k', v)) -> ( + match Type.Id.provably_equal k k' with + | None -> assert false + | Some Type.Equal -> Some v) +end + +type t = { + init_context : context -> Doc.t -> unit; + inline : inline; + block : block; + doc : doc; +} + +and context = { + renderer : t; + mutable state : Dict.t; + b : Buffer.t; + mutable document : Doc.t; +} + +and inline = context -> Inline.t -> bool +and block = context -> Block.t -> bool +and doc = context -> Doc.t -> bool + +let nop _ _ = () +let none _ _ = false + +let make ?(init_context = nop) ?(inline = none) ?(block = none) ?(doc = none) () + = + { init_context; inline; block; doc } + +let compose g f = + let init_context c d = + g.init_context c d; + f.init_context c d + in + let block c b = f.block c b || g.block c b in + let inline c i = f.inline c i || g.inline c i in + let doc c d = f.doc c d || g.doc c d in + { init_context; inline; block; doc } + +let _init_context r = r.init_context +let _inline r = r.inline +let _block r = r.block +let _doc r = r.doc + +module Context = struct + type t = context + let make renderer b = + { renderer; b; state = Dict.empty; document = Doc.empty } + + let buffer c = c.b + let renderer c = c.renderer + let get_document (c : context) = c.document + let get_defs (c : context) = Doc.defs c.document + + module State = struct + type 'a t = 'a Dict.key + let make = Dict.key + let find c st = Dict.find st c.state + let get c st = Option.get (Dict.find st c.state) + let set c st = function + | None -> c.state <- Dict.remove st c.state + | Some s -> c.state <- Dict.add st s c.state + end + + let init c d = c.renderer.init_context c d + + let invalid_inline _ = invalid_arg "Unknown Inline.t case" + let invalid_block _ = invalid_arg "Unknown Block.t case" + let unhandled_doc _ = invalid_arg "Unhandled Doc.t" + + let byte r c = Buffer.add_char r.b c + let utf_8_uchar r u = Buffer.add_utf_8_uchar r.b u + let string c s = Buffer.add_string c.b s + let inline c i = ignore (c.renderer.inline c i || invalid_inline i) + let block c b = ignore (c.renderer.block c b || invalid_block b) + let doc (c : context) d = + c.document <- d; + init c d; + ignore (c.renderer.doc c d || unhandled_doc d); + c.document <- Doc.empty +end + +let doc_to_string r d = + let b = Buffer.create 1024 in + let c = Context.make r b in + Context.doc c d; + Buffer.contents b + +let buffer_add_doc r b d = Context.doc (Context.make r b) d + +type indent = + [ `I of int + | `L of int * string * int * Uchar.t option + | `Q of int + | `Fn of int * Label.t ] + +type state = { + nl : string; (* newline to output. *) + mutable sot : bool; (* start of text *) + mutable indents : indent list; (* indentation stack. *) +} + +let state : state Context.State.t = Context.State.make () +let get_state c = Context.State.get c state +let init_context c d = + Context.State.set c state (Some { nl = Doc.nl d; sot = true; indents = [] }) + +module Char_set = Set.Make (Char) + +let esc_angles = Char_set.of_list [ '<'; '>' ] +let esc_parens = Char_set.of_list [ '('; ')' ] +let esc_quote = Char_set.singleton '\'' +let esc_dquote = Char_set.singleton '\"' +let esc_link_label = Char_set.of_list [ '['; ']'; '\\' ] + +let buffer_add_dec_esc b c = + Buffer.add_string b "&#"; + Buffer.add_string b (Int.to_string (Char.code c)); + Buffer.add_char b ';' + +let buffer_add_bslash_esc b c = + Buffer.add_char b '\\'; + Buffer.add_char b c + +let buffer_add_escaped_string ?(esc_ctrl = true) b cs s = + let flush b max start i = + if start <= max then Buffer.add_substring b s start (i - start) + in + let rec loop b s max start i = + if i > max then flush b max start i + else + let next = i + 1 in + let c = String.get s i in + if Char_set.mem c cs then ( + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next next) + else if esc_ctrl && Ascii.is_control c then ( + flush b max start i; + buffer_add_dec_esc b c; + loop b s max next next) + else loop b s max start next + in + loop b s (String.length s - 1) 0 0 + +let escaped_string ?esc_ctrl c cs s = + buffer_add_escaped_string ?esc_ctrl (Context.buffer c) cs s + +let buffer_add_escaped_text b s = + let esc_first b s = + match s.[0] with + | ('-' | '+' | '_' | '=') as c -> + Buffer.add_char b '\\'; + Buffer.add_char b c; + true + | _ -> false + in + let esc_amp s max next = + next <= max && (Ascii.is_letter s.[next] || s.[next] = '#') + in + let esc_tilde s max prev next = + (not (Char.equal prev '~')) && next <= max && s.[next] = '~' + in + let esc_item_marker s i = + if i = 0 || i > 9 (* marker has from 1-9 digits *) then false + else + let k = ref (i - 1) in + while !k >= 0 && Ascii.is_digit s.[!k] do + decr k + done; + !k < 0 + in + let flush b max start i = + if start <= max then Buffer.add_substring b s start (i - start) + in + let rec loop b s max start prev i = + if i > max then flush b max start i + else + let next = i + 1 in + let c = String.get s i in + if Ascii.is_control c then ( + flush b max start i; + buffer_add_dec_esc b c; + loop b s max next c next) + else + match c with + | ('#' | '`') when not (Char.equal prev c) -> + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next c next + | '~' when esc_tilde s max prev next -> + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next c next + | '&' when esc_amp s max next -> + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next c next + | '!' when i = max -> + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next c next + | ('.' | ')') when esc_item_marker s i -> + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next c next + | '\\' | '<' | '>' | '[' | ']' | '*' | '_' | '$' | '|' -> + flush b max start i; + buffer_add_bslash_esc b c; + loop b s max next c next + | _ -> loop b s max start c next + in + let max = String.length s - 1 in + if max < 0 then () + else if esc_first b s then loop b s max 1 s.[0] 1 + else loop b s max 0 '\x00' 0 + +let escaped_text c s = buffer_add_escaped_text (Context.buffer c) s + +let string_node_option c = function + | None -> () + | Some (s, _) -> Context.string c s +let nchars c n char = + for _i = 1 to n do + Context.byte c char + done + +let newline c = + (* Block generally introduce newlines, except the first one. *) + let st = get_state c in + if st.sot then st.sot <- false else Context.string c st.nl + +let push_indent c n = + let st = get_state c in + st.indents <- n :: st.indents +let pop_indent c = + let st = get_state c in + match st.indents with [] -> () | ns -> st.indents <- List.tl ns + +let rec indent c = + let rec loop c acc = function + | [] -> acc + | (`I n as i) :: is -> + nchars c n ' '; + loop c (i :: acc) is + | (`Q n as i) :: is -> + nchars c n ' '; + Context.byte c '>'; + Context.byte c ' '; + loop c (i :: acc) is + | `L (before, m, after, task) :: is -> + nchars c before ' '; + Context.string c m; + nchars c after ' '; + let after = + match task with + | None -> after + | Some u -> + Context.byte c '['; + Context.utf_8_uchar c u; + Context.string c "] "; + after + 4 + in + (* On the next call we'll just indent for the list item *) + loop c (`I (before + String.length m + after) :: acc) is + | `Fn (before, label) :: is -> + nchars c before ' '; + Context.byte c '['; + link_label_lines c (Label.text label); + Context.string c "]:"; + (* On the next call we'll just indent to ^ for the footnote *) + loop c (`I (before + 1) :: acc) is + in + let st = get_state c in + st.indents <- loop c [] (List.rev st.indents) + +and link_label_lines c lines = escaped_tight_block_lines c esc_link_label lines + +and escaped_tight_block_lines c cs = function + | [] -> () + | l :: ls -> + let tight c (blanks, (l, _)) = + Context.string c blanks; + escaped_string c cs l + in + let line c l = + newline c; + indent c; + tight c l + in + tight c l; + List.iter (line c) ls + +let block_lines c = function + | [] -> () + | (l, _) :: ls -> + let line c (l, _) = + newline c; + indent c; + Context.string c l + in + Context.string c l; + List.iter (line c) ls + +let tight_block_lines c = function + | [] -> () + | l :: ls -> + let tight c (blanks, (l, _)) = + Context.string c blanks; + Context.string c l + in + let line c l = + newline c; + indent c; + tight c l + in + tight c l; + List.iter (line c) ls + +let autolink c a = + Context.byte c '<'; + Context.string c (fst (Inline.Autolink.link a)); + Context.byte c '>' + +let break c b = + let layout_before = fst (Inline.Break.layout_before b) in + let layout_after = fst (Inline.Break.layout_after b) in + let before, after = + match Inline.Break.type' b with + | `Soft -> (layout_before, layout_after) + | `Hard -> + ((if layout_before = "" then " " else layout_before), layout_after) + in + Context.string c before; + newline c; + indent c; + Context.string c after + +let code_span c cs = + nchars c (Inline.Code_span.backtick_count cs) '`'; + tight_block_lines c (Inline.Code_span.code_layout cs); + nchars c (Inline.Code_span.backtick_count cs) '`' + +let emphasis c e = + let delim = Inline.Emphasis.delim e and i = Inline.Emphasis.inline e in + let delim = if not (delim = '*' || delim = '_') then '*' else delim in + Context.byte c delim; + Context.inline c i; + Context.byte c delim + +let strong_emphasis c e = + let delim = Inline.Emphasis.delim e and i = Inline.Emphasis.inline e in + let delim = if not (delim = '*' || delim = '_') then '*' else delim in + Context.byte c delim; + Context.byte c delim; + Context.inline c i; + Context.byte c delim; + Context.byte c delim + +let link_title c open_delim title = + match title with + | None -> () + | Some lines -> + let open', close, escapes = + match open_delim with + | '\"' as delim -> (delim, delim, esc_dquote) + | '\'' as delim -> (delim, delim, esc_quote) + | '(' -> ('(', ')', esc_parens) + | _ -> ('\"', '\"', esc_dquote) + in + Context.byte c open'; + escaped_tight_block_lines c escapes lines; + Context.byte c close + +let link_definition c ld = + let layout = Link_definition.layout ld in + block_lines c layout.before_dest; + (match Link_definition.dest ld with + | None -> () + | Some (dest, _) -> + if layout.angled_dest then ( + Context.byte c '<'; + escaped_string c esc_angles dest; + Context.byte c '>') + else escaped_string c esc_parens dest); + if + layout.after_dest = [] + && Option.is_some (Link_definition.dest ld) + && Option.is_some (Link_definition.title ld) + then Context.byte c ' ' (* at least a space is needed *); + block_lines c layout.after_dest; + link_title c layout.title_open_delim (Link_definition.title ld); + block_lines c layout.after_title + +let link c l = + match Inline.Link.reference l with + | `Inline (ld, _) -> + Context.byte c '['; + Context.inline c (Inline.Link.text l); + Context.byte c ']'; + Context.byte c '('; + link_definition c ld; + Context.byte c ')' + | `Ref (`Shortcut, label, _) -> + Context.byte c '['; + link_label_lines c (Label.text label); + Context.byte c ']' + | `Ref (`Collapsed, label, _) -> + Context.byte c '['; + link_label_lines c (Label.text label); + Context.byte c ']'; + Context.string c "[]" + | `Ref (`Full, label, _) -> + Context.byte c '['; + Context.inline c (Inline.Link.text l); + Context.byte c ']'; + Context.byte c '['; + link_label_lines c (Label.text label); + Context.byte c ']' + +let inlines c is = List.iter (Context.inline c) is +let image c l = + Context.byte c '!'; + link c l +let raw_html c h = tight_block_lines c h +let text c t = escaped_text c t + +let strikethrough c s = + let i = Inline.Strikethrough.inline s in + Context.string c "~~"; + Context.inline c i; + Context.string c "~~" + +let math_span c ms = + let sep = if Inline.Math_span.display ms then "$$" else "$" in + Context.string c sep; + tight_block_lines c (Inline.Math_span.tex_layout ms); + Context.string c sep + +let inline c = function + | Inline.Autolink (a, _) -> + autolink c a; + true + | Inline.Break (b, _) -> + break c b; + true + | Inline.Code_span (cs, _) -> + code_span c cs; + true + | Inline.Emphasis (e, _) -> + emphasis c e; + true + | Inline.Image (i, _) -> + image c i; + true + | Inline.Inlines (is, _) -> + inlines c is; + true + | Inline.Link (l, _) -> + link c l; + true + | Inline.Raw_html (html, _) -> + raw_html c html; + true + | Inline.Strong_emphasis (e, _) -> + strong_emphasis c e; + true + | Inline.Text (t, _) -> + text c t; + true + | Inline.Ext_strikethrough (s, _) -> + strikethrough c s; + true + | Inline.Ext_math_span (m, _) -> + math_span c m; + true + | _ -> + Context.string c ""; + true + +let blank_line c l = + newline c; + indent c; + Context.string c l + +let block_quote c bq = + push_indent c (`Q (Block.Block_quote.indent bq)); + Context.block c (Block.Block_quote.block bq); + pop_indent c + +let code_block c cb = + match Block.Code_block.layout cb with + | `Indented -> + newline c; + push_indent c (`I 4); + indent c; + block_lines c (Block.Code_block.code cb); + pop_indent c + | `Fenced f -> + let opening, closing = + match fst f.opening_fence with + | "" -> + let char, len = Block.Code_block.make_fence cb in + let f = String.make len char in + (f, Some f) + | opening -> (opening, Option.map fst f.closing_fence) + in + let info_string = Block.Code_block.info_string cb in + let code = Block.Code_block.code cb in + newline c; + push_indent c (`I f.indent); + indent c; + Context.string c opening; + string_node_option c info_string; + if code <> [] then ( + newline c; + indent c; + block_lines c code); + (match closing with + | None -> () + | Some close -> + newline c; + indent c; + Context.string c close); + pop_indent c + +let heading c h = + newline c; + indent c; + match Block.Heading.layout h with + | `Atx { indent; after_opening; closing } -> + let inline = Block.Heading.inline h in + nchars c indent ' '; + nchars c (Block.Heading.level h) '#'; + if after_opening = "" && not (Inline.is_empty inline) then + Context.byte c ' ' + else Context.string c after_opening; + Context.inline c inline; + Context.string c closing + | `Setext l -> + let u = + match Block.Heading.level h with 1 -> '=' | 2 -> '-' | _ -> '-' + in + nchars c l.leading_indent ' '; + Context.inline c (Block.Heading.inline h); + Context.string c l.trailing_blanks; + newline c; + indent c; + nchars c l.underline_indent ' '; + nchars c (fst l.underline_count) u; + Context.string c l.underline_blanks + +let html_block c h = + newline c; + indent c; + block_lines c h + +let link_reference_definition c ld = + newline c; + indent c; + nchars c (Link_definition.layout ld).indent ' '; + Context.byte c '['; + (match Link_definition.label ld with + | None -> () + | Some label -> escaped_tight_block_lines c esc_link_label (Label.text label)); + Context.string c "]:"; + link_definition c ld + +let unordered_item c marker (i, _) = + let before = Block.List_item.before_marker i in + let after = Block.List_item.after_marker i in + let task = Option.map fst (Block.List_item.ext_task_marker i) in + push_indent c (`L (before, marker, after, task)); + Context.block c (Block.List_item.block i); + pop_indent c + +let ordered_item c sep num (i, _) = + let before = Block.List_item.before_marker i in + let marker = fst (Block.List_item.marker i) in + let marker = if marker = "" then Int.to_string num ^ sep else marker in + let after = Block.List_item.after_marker i in + let task = Option.map fst (Block.List_item.ext_task_marker i) in + push_indent c (`L (before, marker, after, task)); + Context.block c (Block.List_item.block i); + pop_indent c; + num + 1 + +let list c l = + match Block.List'.type' l with + | `Unordered marker -> + let marker = match marker with '*' | '-' | '+' -> marker | _ -> '*' in + let marker = String.make 1 marker in + List.iter (unordered_item c marker) (Block.List'.items l) + | `Ordered (start, sep) -> + let sep = if sep <> '.' && sep <> ')' then '.' else sep in + let sep = String.make 1 sep in + ignore (List.fold_left (ordered_item c sep) start (Block.List'.items l)) + +let paragraph c p = + newline c; + indent c; + nchars c (Block.Paragraph.leading_indent p) ' '; + Context.inline c (Block.Paragraph.inline p); + Context.string c (Block.Paragraph.trailing_blanks p) + +let thematic_break c t = + let ind = Block.Thematic_break.indent t in + let break = Block.Thematic_break.layout t in + let break = if break = "" then "---" else break in + newline c; + indent c; + nchars c ind ' '; + Context.string c break + +let table c t = + let col c (i, (before, after)) = + Context.byte c '|'; + Context.string c before; + Context.inline c i; + Context.string c after + in + let sep c ((align, len), _) = + Context.byte c '|'; + match align with + | None -> nchars c len '-' + | Some `Left -> + Context.byte c ':'; + nchars c len '-' + | Some `Center -> + Context.byte c ':'; + nchars c len '-'; + Context.byte c ':' + | Some `Right -> + nchars c len '-'; + Context.byte c ':' + in + let row c = function + | (`Header cols, _), blanks | (`Data cols, _), blanks -> + newline c; + indent c; + if cols = [] then Context.byte c '|' else List.iter (col c) cols; + Context.byte c '|'; + Context.string c blanks + | (`Sep seps, _), blanks -> + newline c; + indent c; + if seps = [] then Context.byte c '|' else List.iter (sep c) seps; + Context.byte c '|'; + Context.string c blanks + in + push_indent c (`I (Block.Table.indent t)); + List.iter (row c) (Block.Table.rows t); + pop_indent c + +let footnote c fn = + push_indent c (`Fn (Block.Footnote.indent fn, Block.Footnote.label fn)); + Context.block c (Block.Footnote.block fn); + pop_indent c + +let block c = function + | Block.Blank_line (l, _) -> + blank_line c l; + true + | Block.Block_quote (b, _) -> + block_quote c b; + true + | Block.Blocks (bs, _) -> + List.iter (Context.block c) bs; + true + | Block.Code_block (cb, _) -> + code_block c cb; + true + | Block.Heading (h, _) -> + heading c h; + true + | Block.Html_block (h, _) -> + html_block c h; + true + | Block.Link_reference_definition (ld, _) -> + link_reference_definition c ld; + true + | Block.List (l, _) -> + list c l; + true + | Block.Paragraph (p, _) -> + paragraph c p; + true + | Block.Thematic_break (t, _) -> + thematic_break c t; + true + | Block.Ext_math_block (cb, _) -> + code_block c cb; + true + | Block.Ext_table (t, _) -> + table c t; + true + | Block.Ext_footnote_definition (t, _) -> + footnote c t; + true + | _ -> + newline c; + indent c; + Context.string c ""; + true + +let doc c d = + Context.block c (Doc.block d); + true + +let renderer () = make ~init_context ~inline ~block ~doc () diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 04736983a9..eee8939f61 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1322,7 +1322,8 @@ module Odoc_markdown_cmd = Make_renderer (struct (* QUESTION: Where is this being used? *) let filepath config url = Odoc_markdown.Generator.filepath ~config url - let extra_args = Term.const { Odoc_markdown.Config.root_url = None } + let extra_args = + Term.const { Odoc_markdown.Config.root_url = None; allow_html = true } let renderer = { Odoc_document.Renderer.name = "markdown"; render; filepath } end) From 74b58c17397425c9ddafa49f7835b92b3befda27 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 15:14:54 +0200 Subject: [PATCH 33/53] Expose Config and Generator --- src/markdown2/odoc_markdown.ml | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/markdown2/odoc_markdown.ml b/src/markdown2/odoc_markdown.ml index ff2edbd09c..b5fe50350e 100644 --- a/src/markdown2/odoc_markdown.ml +++ b/src/markdown2/odoc_markdown.ml @@ -1,4 +1,2 @@ module Config = Config -module Markdown_page = Markdown_page module Generator = Generator -module Link = Link From 8925c545711b9f58ede9bbda936fa9fe7def894d Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 17:41:13 +0200 Subject: [PATCH 34/53] Install cmarkit on 4.14 --- odoc.opam | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/odoc.opam b/odoc.opam index b6425ce4ae..68243e9a78 100644 --- a/odoc.opam +++ b/odoc.opam @@ -51,7 +51,7 @@ depends: [ "tyxml" {>= "4.4.0"} "fmt" "crunch" {>= "1.4.1"} - + "cmarkit" {>= "0.3.0" & ocaml:version >= "4.14"} "ocamlfind" {with-test} "yojson" {>= "2.1.0" & with-test} "sexplib0" {with-test} From f8b767a1cc4b17c83b0db6d160b03a4d467ce1e8 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 18:04:54 +0200 Subject: [PATCH 35/53] remove 'tree' from cram --- test/integration/markdown-with-belt.t/run.t | 8 -------- 1 file changed, 8 deletions(-) diff --git a/test/integration/markdown-with-belt.t/run.t b/test/integration/markdown-with-belt.t/run.t index 419db6aa24..5ef11363bb 100644 --- a/test/integration/markdown-with-belt.t/run.t +++ b/test/integration/markdown-with-belt.t/run.t @@ -9,14 +9,6 @@ $ odoc markdown-generate Belt.odocl -o markdown $ odoc markdown-generate Belt_Id.odocl -o markdown - $ tree markdown - markdown - `-- Belt - |-- Belt.md - `-- Belt_Id.md - - 1 directory, 2 files - $ cat markdown/Belt/Belt.md # Module `Belt` From f053490d1d943d836903fd01393f5989ced53a75 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 18:56:16 +0200 Subject: [PATCH 36/53] Use cppo to hide Generator from dune build --- src/markdown2/dune | 11 ++++++++++- src/markdown2/odoc_markdown.cppo.ml | 16 ++++++++++++++++ src/markdown2/odoc_markdown.ml | 2 -- 3 files changed, 26 insertions(+), 3 deletions(-) create mode 100644 src/markdown2/odoc_markdown.cppo.ml delete mode 100644 src/markdown2/odoc_markdown.ml diff --git a/src/markdown2/dune b/src/markdown2/dune index 2836410dcf..e1f532268a 100644 --- a/src/markdown2/dune +++ b/src/markdown2/dune @@ -1,4 +1,13 @@ (library (name odoc_markdown) (public_name odoc.markdown) - (libraries odoc_model odoc_document cmarkit)) + (libraries odoc_model odoc_document cmarkit) + (preprocess + (action + (run + %{bin:cppo} + -I + "%{env:CPPO_FLAGS=}" + -V + OCAML:%{ocaml_version} + %{input-file})))) diff --git a/src/markdown2/odoc_markdown.cppo.ml b/src/markdown2/odoc_markdown.cppo.ml new file mode 100644 index 0000000000..3cb2ba4ed0 --- /dev/null +++ b/src/markdown2/odoc_markdown.cppo.ml @@ -0,0 +1,16 @@ +module Config = Config + +#if OCAML_VERSION >= (4, 08, 0) +module Generator = Generator +#else +module Generator = struct + let render (_ : Config.t) _ = failwith "Markdown generation isn't available" + + let filepath (_ : Config.t) _ = failwith "Markdown generation isn't available" + + let items (_ : Config.t) _ = failwith "Markdown generation isn't available" + + let inline (_ : Config.t) _ = failwith "Markdown generation isn't available" +end +#endif + diff --git a/src/markdown2/odoc_markdown.ml b/src/markdown2/odoc_markdown.ml deleted file mode 100644 index b5fe50350e..0000000000 --- a/src/markdown2/odoc_markdown.ml +++ /dev/null @@ -1,2 +0,0 @@ -module Config = Config -module Generator = Generator From 1939a1b1f5dda3875b6f7a0d788fcd8a6b65c18b Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 8 May 2025 21:32:44 +0200 Subject: [PATCH 37/53] Remove copyright from markdown generation --- src/markdown2/markdown_page.ml | 16 ---------------- src/markdown2/markdown_page.mli | 16 ---------------- 2 files changed, 32 deletions(-) diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index e227c919e1..6257958417 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -1,19 +1,3 @@ -(* - * Copyright (c) 2016 Thomas Refis - * - * Permission to use, copy, modify, and distribute this software for any - * purpose with or without fee is hereby granted, provided that the above - * copyright notice and this permission notice appear in all copies. - * - * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - *) - module Url = Odoc_document.Url let make ~config ~url doc children = diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index 265dc41ac5..957e037114 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -1,19 +1,3 @@ -(* - * Copyright (c) 2016 Thomas Refis - * - * Permission to use, copy, modify, and distribute this software for any - * purpose with or without fee is hereby granted, provided that the above - * copyright notice and this permission notice appear in all copies. - * - * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - *) - (** Supported languages for printing code parts. *) (** {1 Page creator} *) From a6590c4720a9a07616f5b58fa3f409bbbe54185b Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 9 May 2025 12:44:47 +0200 Subject: [PATCH 38/53] Simplify rendering --- src/markdown2/generator.ml | 200 ++--- src/markdown2/markdown_page.ml | 12 +- src/markdown2/markdown_page.mli | 2 +- src/markdown2/renderer.ml | 1354 +++++-------------------------- 4 files changed, 278 insertions(+), 1290 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 83bb7a24a9..8174b20448 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -6,12 +6,6 @@ module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url module Link = HLink -(* TODO: Remove Md module *) -module Md = struct - include Renderer - let meta = Renderer.Meta.none -end - let source fn (t : Types.Source.t) = let rec token (x : Types.Source.token) = match x with Elt i -> fn i | Tag (_, l) -> tokens l @@ -21,14 +15,12 @@ let source fn (t : Types.Source.t) = and styled style content = match style with | `Bold -> - let inlines_as_one_inline = Md.Inline.Inlines (content, Md.meta) in - let emphasis = Md.Inline.Emphasis.make inlines_as_one_inline in - [ Md.Inline.Strong_emphasis (emphasis, Md.meta) ] + let inlines_as_one_inline = Renderer.Inline.Inlines content in + [ Renderer.Inline.Strong_emphasis inlines_as_one_inline ] | `Italic | `Emphasis -> (* We treat emphasis as italic, since there's no difference in Markdown *) - let inlines_as_one_inline = Md.Inline.Inlines (content, Md.meta) in - let emphasis = Md.Inline.Emphasis.make inlines_as_one_inline in - [ Md.Inline.Emphasis (emphasis, Md.meta) ] + let inlines_as_one_inline = Renderer.Inline.Inlines content in + [ Renderer.Inline.Emphasis inlines_as_one_inline ] | `Superscript | `Subscript -> (* CommonMark doesn't have support for superscript/subscript, render the content as inline *) content @@ -63,29 +55,27 @@ and block_text_only blocks : string list = and inline ~(config : Config.t) ~resolve l = let one (t : Types.Inline.one) = match t.desc with - | Text s -> [ Md.Inline.Text (s, Md.meta) ] + | Text s -> [ Renderer.Inline.Text s ] | Entity s -> (* In CommonMark, HTML entities are supported directly, so we can just output them as text *) - [ Md.Inline.Text (s, Md.meta) ] - | Linebreak -> - let break = Md.Inline.Break.make `Hard in - [ Md.Inline.Break (break, Md.meta) ] + [ Renderer.Inline.Text s ] + | Linebreak -> [ Renderer.Inline.Break ] | Styled (style, c) -> let inline_content = inline ~config ~resolve c in styled style inline_content | Link link -> inline_link ~config ~resolve link | Source c -> (* CommonMark doesn't allow any complex node inside inline text, rendering inline nodes as text *) - let content = String.concat ~sep:"" (source inline_text_only c) in - [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] + let content = source inline_text_only c in + [ Renderer.Inline.Code_span content ] | Math s -> (* Since CommonMark doesn't support Math's, we just treat it as code. Maybe could use Ext_math_block or Ext_math_display *) - [ Md.Inline.Code_span (Md.Inline.Code_span.of_string s, Md.meta) ] + [ Renderer.Inline.Code_span [ s ] ] | Raw_markup (target, content) -> ( match Astring.String.Ascii.lowercase target with | "html" -> - let block_lines = Md.Block_line.tight_list_of_string content in - [ Md.Inline.Raw_html (block_lines, Md.meta) ] + let block_lines = content in + [ Renderer.Inline.Raw_html [ block_lines ] ] | another_lang -> (* TODO: Is this correct? *) let msg = @@ -108,93 +98,84 @@ and inline_link ~config ~resolve link = match href with | Some href -> let inline_content = inline ~config ~resolve link.content in - let link_inline = Md.Inline.Inlines (inline_content, Md.meta) in - let link_definition = Md.Link_definition.make ~dest:(href, Md.meta) () in - let link_reference = `Inline (link_definition, Md.meta) in - let inline_link = Md.Inline.Link.make link_inline link_reference in - [ Md.Inline.Link (inline_link, Md.meta) ] - | None -> - let content = String.concat ~sep:"" (inline_text_only link.content) in - [ Md.Inline.Code_span (Md.Inline.Code_span.of_string content, Md.meta) ] + let link_inline = Renderer.Inline.Inlines inline_content in + let link_definition = Renderer.Link_definition.make ~dest:href () in + let inline_link : Renderer.Inline.link = + { text = link_inline; reference = link_definition } + in + [ Renderer.Inline.Link inline_link ] + | None -> [ Renderer.Inline.Code_span (inline_text_only link.content) ] let rec block ~config ~resolve l = let one (t : Types.Block.one) = match t.desc with | Paragraph paragraph -> let inlines = inline ~config ~resolve paragraph in - let inlines = Md.Inline.Inlines (inlines, Md.meta) in - let paragraph_block = - Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) - in + let inlines = Renderer.Inline.Inlines inlines in + let paragraph_block = Renderer.Block.Paragraph inlines in (* CommonMark treats paragraph as a block, to align the behavior with other generators such as HTML, we add a blank line after it *) - let break = Md.Block.Blank_line ("", Md.meta) in + let break = Renderer.Block.Blank_line in [ paragraph_block; break ] | List (typ, l) -> let list_type = match typ with - | Ordered -> `Ordered (1, '.') - | Unordered -> `Unordered '-' + | Ordered -> Renderer.Block.Ordered + | Unordered -> Renderer.Block.Unordered in let list_items = List.map (fun items -> let block = block ~config ~resolve items in - let blocks = Md.Block.Blocks (block, Md.meta) in - (Md.Block.List_item.make blocks, Md.meta)) + let blocks = Renderer.Block.Blocks block in + blocks) l in [ (* TODO: Do we need the list ~tight:false based on surrounding content or can we always be ~tight:true? *) - Md.Block.List - (Md.Block.List'.make ~tight:true list_type list_items, Md.meta); + Renderer.Block.List + { type_ = list_type; tight = true; items = list_items }; ] | Inline i -> - let inlines = Md.Inline.Inlines (inline ~config ~resolve i, Md.meta) in - [ Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) ] + let inlines = Renderer.Inline.Inlines (inline ~config ~resolve i) in + [ Renderer.Block.Paragraph inlines ] | Table t -> block_table t | Description l -> let item ({ key; definition; attr = _ } : Types.Description.one) = let term = inline ~config ~resolve key in (* We extract definition as inline, since it came as "Block". There seems to be no way (in Cmarkit) to make it inline *) let definition_inline = - Md.Inline.Text - (String.concat ~sep:"" (block_text_only definition), Md.meta) + Renderer.Inline.Text + (String.concat ~sep:"" (block_text_only definition)) in - let space = Md.Inline.Text (" ", Md.meta) in + let space = Renderer.Inline.Text " " in let term_inline = - Md.Inline.Inlines (term @ [ space; definition_inline ], Md.meta) + Renderer.Inline.Inlines (term @ [ space; definition_inline ]) in - [ Md.Block.Paragraph (Md.Block.Paragraph.make term_inline, Md.meta) ] + [ Renderer.Block.Paragraph term_inline ] in List.concat_map item l | Verbatim s -> let code_snippet = - Md.Block.Code_block - (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) + Renderer.Block.Code_block { info_string = None; code = [ s ] } in [ code_snippet ] | Source (lang, s) -> - let code_block = - s |> source inline_text_only |> List.map (fun s -> (s, Md.meta)) - in - let info_string = (lang, Md.meta) in + let code = s |> source inline_text_only |> List.map (fun s -> s) in let code_snippet = - Md.Block.Code_block - (Md.Block.Code_block.make ~info_string code_block, Md.meta) + Renderer.Block.Code_block { info_string = Some lang; code } in [ code_snippet ] | Math s -> (* Since CommonMark doesn't support Math's, we just treat it as code. Maybe could use Ext_math_block or Ext_math_display *) let block = - Md.Block.Code_block - (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) + Renderer.Block.Code_block { info_string = None; code = [ s ] } in [ block ] | Raw_markup (target, content) -> ( match Astring.String.Ascii.lowercase target with | "html" -> - let block_lines = Md.Block_line.list_of_string content in - [ Md.Block.Html_block (block_lines, Md.meta) ] + let block_lines = Renderer.Block_line.list_of_string content in + [ Renderer.Block.Html_block block_lines ] | another_lang -> (* TODO: Is this correct? *) let msg = @@ -211,25 +192,23 @@ let rec block ~config ~resolve l = | Image (target, alt) -> let dest = match (target : Types.Target.t) with - | External url -> (url, Md.meta) + | External url -> url | Internal (Resolved uri) -> let url = Link.href ~config ~resolve uri in - (url, Md.meta) + url | Internal Unresolved -> (* TODO: What's unresolved? A non-existing page/link? *) - ("", Md.meta) + "" in - let image = - Md.Inline.Link.make - (Md.Inline.Text (alt, Md.meta)) - (`Inline (Md.Link_definition.make ~dest (), Md.meta)) + let image : Renderer.Inline.link = + { + text = Renderer.Inline.Text alt; + reference = Renderer.Link_definition.make ~dest (); + } in [ - Md.Block.Paragraph - ( Md.Block.Paragraph.make - (Md.Inline.Inlines - ([ Md.Inline.Image (image, Md.meta) ], Md.meta)), - Md.meta ); + Renderer.Block.Paragraph + (Renderer.Inline.Inlines [ Renderer.Inline.Image image ]); ] in List.concat_map one l @@ -252,10 +231,7 @@ and block_table t = in if rows_data = [] then - [ - Md.Block.Paragraph - (Md.Block.Paragraph.make (Md.Inline.Inlines ([], Md.meta)), Md.meta); - ] + [ Renderer.Block.Paragraph (Renderer.Inline.Inlines []) ] else let max_columns = List.fold_left @@ -297,8 +273,8 @@ and block_table t = let header_inline = let header_text = "| " ^ String.concat ~sep:" | " header_cells ^ " |" in - let header_md = Md.Inline.Text (header_text, Md.meta) in - Md.Inline.Inlines ([ header_md ], Md.meta) + let header_md = Renderer.Inline.Text header_text in + Renderer.Inline.Inlines [ header_md ] in (* Create the separator row (based on column alignment) *) @@ -327,8 +303,8 @@ and block_table t = alignments in let sep_text = "| " ^ String.concat ~sep:" | " separator_cells ^ " |" in - let sep_md = Md.Inline.Text (sep_text, Md.meta) in - Md.Inline.Inlines ([ sep_md ], Md.meta) + let sep_md = Renderer.Inline.Text sep_text in + Renderer.Inline.Inlines [ sep_md ] in let content_inlines = @@ -336,16 +312,15 @@ and block_table t = (fun row -> let cells = pad_row row in let row_text = "| " ^ String.concat ~sep:" | " cells ^ " |" in - let row_md = Md.Inline.Text (row_text, Md.meta) in - Md.Inline.Inlines ([ row_md ], Md.meta)) + let row_md = Renderer.Inline.Text row_text in + Renderer.Inline.Inlines [ row_md ]) content_rows in List.map - (fun inline -> - Md.Block.Paragraph (Md.Block.Paragraph.make inline, Md.meta)) + (fun inline -> Renderer.Block.Paragraph inline) ([ header_inline; separator_inline ] @ content_inlines) -and items ~config ~resolve l : Md.Block.t list = +and items ~config ~resolve l : Renderer.Block.t list = let rec walk_items acc (t : Types.Item.t list) = let continue_with rest elts = (walk_items [@tailcall]) (List.rev_append elts acc) rest @@ -362,11 +337,13 @@ and items ~config ~resolve l : Md.Block.t list = (continue_with [@tailcall]) rest content | Heading h :: rest -> (* Markdown headings are rendered as a blank line before and after the heading, otherwise it treats it as an inline paragraph *) - let break = Md.Block.Blank_line ("", Md.meta) in + let break = Renderer.Block.Blank_line in let inlines = inline ~config ~resolve h.title in - let content = Md.Inline.Inlines (inlines, Md.meta) in - let block = Md.Block.Heading.make ~level:(h.level + 1) content in - let heading_block = Md.Block.Heading (block, Md.meta) in + let content = Renderer.Inline.Inlines inlines in + let block : Renderer.Block.heading = + { level = h.level + 1; inline = content; id = None } + in + let heading_block = Renderer.Block.Heading block in (continue_with [@tailcall]) rest [ break; heading_block; break ] | Include { @@ -412,22 +389,17 @@ and documentedSrc ~config ~resolve t = Accum [ { attrs; anchor; code = `N code; doc; markers } ] | _ -> Stop_and_keep) in - let rec to_markdown t : Md.Block.t list = + let rec to_markdown t : Renderer.Block.t list = match t with | [] -> [] | (Code _ | Alternative _) :: _ -> let code, header, rest = take_code t in let info_string = - match header with - | Some header -> Some (header, Md.meta) - | None -> None + match header with Some header -> Some header | None -> None in let inline_source = source inline_text_only code in - let code_block = [ (String.concat ~sep:"" inline_source, Md.meta) ] in - let block = - Md.Block.Code_block - (Md.Block.Code_block.make ?info_string code_block, Md.meta) - in + let code = [ String.concat ~sep:"" inline_source ] in + let block = Renderer.Block.Code_block { info_string; code } in [ block ] @ to_markdown rest | Subpage subp :: _ -> subpage ~config ~resolve subp | (Documented _ | Nested _) :: _ -> @@ -437,10 +409,8 @@ and documentedSrc ~config ~resolve t = match code with | `D code -> let inline_source = inline ~config ~resolve code in - let inlines = Md.Inline.Inlines (inline_source, Md.meta) in - let block = - Md.Block.Paragraph (Md.Block.Paragraph.make inlines, Md.meta) - in + let inlines = Renderer.Inline.Inlines inline_source in + let block = Renderer.Block.Paragraph inlines in [ block ] | `N n -> to_markdown n in @@ -467,7 +437,7 @@ module Page = struct and subpages ~config subpages = List.map (include_ ~config) subpages - and page ~config p : Odoc_document.Renderer.page = + and page ~config p = (* TODO: disambiguate the page? *) let subpages = subpages ~config @@ Doctree.Subpages.compute p in let resolve = Link.Current p.url in @@ -478,8 +448,8 @@ module Page = struct let header = items ~config ~resolve header in let preamble = items ~config ~resolve preamble in let content = items ~config ~resolve i in - let root_block = Md.Block.Blocks (header @ preamble @ content, Md.meta) in - let doc = Md.Doc.make root_block in + let root_block = Renderer.Block.Blocks (header @ preamble @ content) in + let doc = root_block in Markdown_page.make ~config ~url:p.url doc subpages and source_page ~config sp = @@ -495,8 +465,7 @@ module Page = struct match doc with | Types.Source_page.Plain_code s -> let plain_code = - Md.Block.Code_block - (Md.Block.Code_block.make [ (s, Md.meta) ], Md.meta) + Renderer.Block.Code_block { info_string = None; code = [ s ] } in [ plain_code ] | Tagged_code (info, docs) -> ( @@ -504,23 +473,22 @@ module Page = struct match info with | Syntax tok -> let syntax = - Md.Block.Code_block - (Md.Block.Code_block.make [ (tok, Md.meta) ], Md.meta) + Renderer.Block.Code_block + { info_string = Some tok; code = [ tok ] } in - [ syntax; Md.Block.Blocks (childrens, Md.meta) ] + [ syntax; Renderer.Block.Blocks childrens ] | Link { documentation = _; implementation = None } -> childrens | Link { documentation = _; implementation = Some anchor } -> let name = anchor.page.name in - let inline_name = Md.Inline.Text (name, Md.meta) in + let inline_name = Renderer.Inline.Text name in let href = Link.href ~config ~resolve anchor in let link_definition = - Md.Link_definition.make ~dest:(href, Md.meta) () + Renderer.Link_definition.make ~dest:href () in - let link_reference = `Inline (link_definition, Md.meta) in - let inline_link = - Md.Inline.Link.make inline_name link_reference + let inline_link : Renderer.Inline.link = + { text = inline_name; reference = link_definition } in - let _ = [ Md.Inline.Link (inline_link, Md.meta) ] in + let _ = [ Renderer.Inline.Link inline_link ] in childrens | Anchor _lbl -> childrens) in diff --git a/src/markdown2/markdown_page.ml b/src/markdown2/markdown_page.ml index ecce36ae87..8a00f50272 100644 --- a/src/markdown2/markdown_page.ml +++ b/src/markdown2/markdown_page.ml @@ -18,18 +18,14 @@ module Url = Odoc_document.Url let make ~config ~url doc children = let filename = Link.Path.as_filename ~config url in - let content ppf = - let renderer = Renderer.renderer () in - Format.fprintf ppf "%s" (Renderer.doc_to_string renderer doc) - in + let content ppf = Format.fprintf ppf "%s" (Renderer.to_string doc) in { Odoc_document.Renderer.filename; content; children; path = url } let make_src ~config ~url _title block_list = let filename = Link.Path.as_filename ~config url in let content (ppf : Format.formatter) = - let renderer = Renderer.renderer () in - let root_block = Renderer.Block.Blocks (block_list, Renderer.Meta.none) in - let doc = Renderer.Doc.make root_block in - Format.fprintf ppf "%s" (Renderer.doc_to_string renderer doc) + let root_block = Renderer.Block.Blocks block_list in + let doc = root_block in + Format.fprintf ppf "%s" (Renderer.to_string doc) in { Odoc_document.Renderer.filename; content; children = []; path = url } diff --git a/src/markdown2/markdown_page.mli b/src/markdown2/markdown_page.mli index e21b6d9ab5..3dfa25e3a1 100644 --- a/src/markdown2/markdown_page.mli +++ b/src/markdown2/markdown_page.mli @@ -21,7 +21,7 @@ val make : config:Config.t -> url:Odoc_document.Url.Path.t -> - Renderer.Doc.t -> + Renderer.doc -> Odoc_document.Renderer.page list -> Odoc_document.Renderer.page diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index 0a819668eb..6abc9597f4 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -1,40 +1,24 @@ -module Cmarkit_data = struct - module Uset = struct - include Set.Make (Uchar) - let of_array = - let add acc u = add (Uchar.unsafe_of_int u) acc in - Array.fold_left add empty - end - - module Umap = struct - include Map.Make (Uchar) - let of_array = - let add acc (u, f) = add (Uchar.unsafe_of_int u) f acc in - Array.fold_left add empty - end - - let whitespace_uset = Uset.of_array Data_uchar.whitespace - let punctuation_uset = Uset.of_array Data_uchar.punctuation - let case_fold_umap = Umap.of_array Data_uchar.case_fold - - let unicode_version = Data_uchar.unicode_version - let is_unicode_whitespace u = Uset.mem u whitespace_uset - let is_unicode_punctuation u = Uset.mem u punctuation_uset - let unicode_case_fold u = Umap.find_opt u case_fold_umap - - (* HTML entity data. *) - - module String_map = Map.Make (String) +(* TODO: What can we do with Uchar / Uset and Umap? *) +(* TODO: What can we do with Ascii? *) + +module Uset = struct + include Set.Make (Uchar) + let of_array = + let add acc u = add (Uchar.unsafe_of_int u) acc in + Array.fold_left add empty end -(* TODO: Remove Meta module *) -module Meta = struct - type t = unit - let none = () +module Umap = struct + include Map.Make (Uchar) + let of_array = + let add acc (u, f) = add (Uchar.unsafe_of_int u) f acc in + Array.fold_left add empty end -(* TODO: Remove Meta.t from node *) -type 'a node = 'a * Meta.t +let case_fold_umap = Umap.of_array Data_uchar.case_fold +let unicode_case_fold u = Umap.find_opt u case_fold_umap +let punctuation_uset = Uset.of_array Data_uchar.punctuation +let is_unicode_punctuation u = Uset.mem u punctuation_uset module Ascii = struct let is_control = function '\x00' .. '\x1F' | '\x7F' -> true | _ -> false @@ -172,16 +156,6 @@ module Match = struct else atext_seq s last (start + 1) end -module Layout = struct - type blanks = string - type nonrec string = string - type nonrec char = char - type count = int - type indent = int - let string ?(meta = Meta.none) s = (s, meta) - let empty = string "" -end - module Block_line = struct let _list_of_string flush s = (* cuts [s] on newlines *) @@ -200,96 +174,51 @@ module Block_line = struct in loop s [] (String.length s - 1) 0 0 - let flush ?(meta = Meta.none) s start last acc = + let flush s start last acc = let sub = String.sub s start (last - start + 1) in - (sub, meta) :: acc + sub :: acc - let flush_tight ?(meta = Meta.none) s start last acc = + (* let flush_tight s start last acc = (* If [s] has newlines, blanks after newlines are layout *) - if start > last then ("", ("", meta)) :: acc + if start > last then "" :: acc else match acc with | [] (* On the first line the blanks are legit *) -> - ("", (String.sub s start (last - start + 1), meta)) :: acc + String.sub s start (last - start + 1) :: acc | acc -> let nb = Match.first_non_blank s ~last ~start in - ( String.sub s start (nb - 1 - start + 1), - (String.sub s nb (last - nb + 1), meta) ) + String.sub s start (nb - 1 - start + 1) + :: String.sub s nb (last - nb + 1) :: acc - + *) (* Block lines *) - type t = string node - let to_string = fst - let list_of_string ?meta s = _list_of_string (flush ?meta) s + let list_of_string s = _list_of_string flush s (* Tight lines *) - type tight = Layout.blanks * t + type tight = string - let tight_to_string l = fst (snd l) - let tight_list_of_string ?meta s = _list_of_string (flush_tight ?meta) s + (* let tight_list_of_string s = _list_of_string flush_tight s *) (* Blank lines *) - - type blank = Layout.blanks node end +(* TODO: What's label? *) module Label = struct type key = string - type t = { meta : Meta.t; key : key; text : Block_line.tight list } - let make ?(meta = Meta.none) ~key text = { key; text; meta } - let with_meta meta l = { l with meta } - let meta t = t.meta + type t = { key : key; text : Block_line.tight list } + let make ~key text = { key; text } let key t = t.key let text t = t.text - let text_to_string t = - String.concat " " (List.map Block_line.tight_to_string t.text) + let text_to_string t = String.concat " " t.text let compare l0 l1 = String.compare l0.key l1.key - - (* Definitions *) - - module Map = Map.Make (String) - type def = .. - type defs = def Map.t - - (* Resolvers *) - - type context = - [ `Def of t option * t | `Ref of [ `Link | `Image ] * t * t option ] - - type resolver = context -> t option - let default_resolver = function - | `Def (None, k) -> Some k - | `Def (Some _, _k) -> None - | `Ref (_, _, k) -> k end module Link_definition = struct - type layout = { - indent : Layout.indent; - angled_dest : bool; - before_dest : Block_line.blank list; - after_dest : Block_line.blank list; - title_open_delim : Layout.char; - after_title : Block_line.blank list; - } - - let layout_for_dest dest = - let needs_angles c = Ascii.is_control c || c = ' ' in - let angled_dest = String.exists needs_angles dest in - { - indent = 0; - angled_dest; - before_dest = []; - after_dest = []; - title_open_delim = '\"'; - after_title = []; - } - - let default_layout = + (* let default_layout = { indent = 0; angled_dest = false; @@ -297,607 +226,88 @@ module Link_definition = struct after_dest = []; title_open_delim = '\"'; after_title = []; - } + } *) type t = { - layout : layout; label : Label.t option; defined_label : Label.t option; - dest : string node option; + dest : string option; title : Block_line.tight list option; } let make ?defined_label ?label ?dest ?title () = - let layout = - match dest with - | None -> default_layout - | Some (d, _) -> layout_for_dest d - in let defined_label = match defined_label with None -> label | Some d -> d in - { layout; label; defined_label; dest; title } - - let layout ld = ld.layout + { label; defined_label; dest; title } let label ld = ld.label let defined_label ld = ld.defined_label let dest ld = ld.dest let title ld = ld.title - - type Label.def += Def of t node end module Inline = struct - type t = .. - - module Autolink = struct - type t = { is_email : bool; link : string node } - let is_email a = a.is_email - let link a = a.link - let make link = - let is_email = - let l = String.concat "" [ "<"; fst link; ">" ] in - match Match.autolink_email l ~last:(String.length l - 1) ~start:0 with - | None -> false - | Some _ -> true - in - { is_email; link } - end - - module Break = struct - type type' = [ `Hard | `Soft ] - type t = { - layout_before : Layout.blanks node; - type' : type'; - layout_after : Layout.blanks node; - } - - let make ?(layout_before = Layout.empty) ?(layout_after = Layout.empty) - type' = - { layout_before; type'; layout_after } - - let type' b = b.type' - let layout_before b = b.layout_before - let layout_after b = b.layout_after - end - - module Code_span = struct - type t = { - backtick_count : Layout.count; - code_layout : Block_line.tight list; - } - - let make ~backtick_count code_layout = { backtick_count; code_layout } - - let min_backtick_count ~min counts = - let rec loop min = function - | c :: cs -> if min <> c then min else loop (c + 1) cs - | [] -> min - in - loop min (List.sort Int.compare counts) - - let of_string ?(meta = Meta.none) = function - | "" -> { backtick_count = 1; code_layout = [ ("", ("", meta)) ] } - | s -> - (* This finds out the needed backtick count, whether spaces are needed, - and treats blanks after newline as layout *) - let max = String.length s - 1 in - let need_sp = s.[0] = '`' || s.[max] = '`' in - let s = if need_sp then String.concat "" [ " "; s; " " ] else s in - let backtick_counts, code_layout = - let rec loop bt_counts acc max btc start k = - match k > max with - | true -> - (* assert (btc = 0) because of [need_sp] *) - ( bt_counts, - if acc = [] then [ ("", (s, meta)) ] - else List.rev (Block_line.flush_tight ~meta s start max acc) - ) - | false -> - if s.[k] = '`' then - loop bt_counts acc max (btc + 1) start (k + 1) - else - let bt_counts = - if btc > 0 then btc :: bt_counts else bt_counts - in - if not (s.[k] = '\n' || s.[k] = '\r') then - loop bt_counts acc max 0 start (k + 1) - else - let acc = - Block_line.flush_tight ~meta s start (k - 1) acc - in - let start = - if k + 1 <= max && s.[k] = '\r' && s.[k + 1] = '\n' then - k + 2 - else k + 1 - in - loop bt_counts acc max 0 start start - in - loop [] [] max 0 0 0 - in - let backtick_count = min_backtick_count ~min:1 backtick_counts in - { backtick_count; code_layout } - - let backtick_count cs = cs.backtick_count - let code_layout cs = cs.code_layout - let code cs = - (* Extract code, see https://spec.commonmark.org/0.30/#code-spans *) - let sp c = Char.equal c ' ' in - let s = List.map Block_line.tight_to_string cs.code_layout in - let s = String.concat " " s in - if s = "" then "" - else if - s.[0] = ' ' - && s.[String.length s - 1] = ' ' - && not (String.for_all sp s) - then String.sub s 1 (String.length s - 2) - else s - end - - module Emphasis = struct - type inline = t - type t = { delim : Layout.char; inline : inline } - let make ?(delim = '*') inline = { delim; inline } - let inline e = e.inline - let delim e = e.delim - end - - module Link = struct - type inline = t - - type reference_layout = [ `Collapsed | `Full | `Shortcut ] - type reference = - [ `Inline of Link_definition.t node - | `Ref of reference_layout * Label.t * Label.t ] - - type t = { text : inline; reference : reference } - - let make text reference = { text; reference } - let text l = l.text - let reference l = l.reference - let referenced_label l = - match l.reference with `Inline _ -> None | `Ref (_, _, k) -> Some k - - let reference_definition defs l = - match l.reference with - | `Inline ld -> Some (Link_definition.Def ld) - | `Ref (_, _, def) -> Label.Map.find_opt (Label.key def) defs - - let is_unsafe l = - let allowed_data_url l = - let allowed = - [ "image/gif"; "image/png"; "image/jpeg"; "image/webp" ] - in - (* Extract mediatype from data:[][;base64], *) - match String.index_from_opt l 4 ',' with - | None -> false - | Some j -> - let k = - match String.index_from_opt l 4 ';' with None -> j | Some k -> k - in - let t = String.sub l 5 (min j k - 5) in - List.mem t allowed - in - Ascii.caseless_starts_with ~prefix:"javascript:" l - || Ascii.caseless_starts_with ~prefix:"vbscript:" l - || Ascii.caseless_starts_with ~prefix:"file:" l - || Ascii.caseless_starts_with ~prefix:"data:" l - && not (allowed_data_url l) - end - - module Raw_html = struct - type t = Block_line.tight list - end - - module Text = struct - type t = string - end - - type t += - | Autolink of Autolink.t node - | Break of Break.t node - | Code_span of Code_span.t node - | Emphasis of Emphasis.t node - | Image of Link.t node - | Inlines of t list node - | Link of Link.t node - | Raw_html of Raw_html.t node - | Strong_emphasis of Emphasis.t node - | Text of Text.t node - - let empty = Inlines ([], Meta.none) - - let err_unknown = "Unknown Cmarkit.Inline.t type extension" - - (* Extensions *) - - module Strikethrough = struct - type nonrec t = t - let make = Fun.id - let inline = Fun.id - end - - module Math_span = struct - type t = { display : bool; tex_layout : Block_line.tight list } - let make ~display tex_layout = { display; tex_layout } - let display ms = ms.display - let tex_layout ms = ms.tex_layout - let tex ms = - let s = List.map Block_line.tight_to_string ms.tex_layout in - String.concat " " s - end - - type t += - | Ext_strikethrough of Strikethrough.t node - | Ext_math_span of Math_span.t node - - (* Functions on inlines *) - - let is_empty = function Text ("", _) | Inlines ([], _) -> true | _ -> false - - let ext_none _ = invalid_arg err_unknown - let meta ?(ext = ext_none) = function - | Autolink (_, m) - | Break (_, m) - | Code_span (_, m) - | Emphasis (_, m) - | Image (_, m) - | Inlines (_, m) - | Link (_, m) - | Raw_html (_, m) - | Strong_emphasis (_, m) - | Text (_, m) -> - m - | Ext_strikethrough (_, m) -> m - | Ext_math_span (_, m) -> m - | i -> ext i - - let rec normalize ?(ext = ext_none) = function - | ( Autolink _ | Break _ | Code_span _ | Raw_html _ | Text _ - | Inlines ([], _) - | Ext_math_span _ ) as i -> - i - | Image (l, m) -> Image ({ l with text = normalize ~ext l.text }, m) - | Link (l, m) -> Link ({ l with text = normalize ~ext l.text }, m) - | Inlines ([ i ], _) -> i - | Emphasis (e, m) -> - Emphasis ({ e with inline = normalize ~ext e.inline }, m) - | Strong_emphasis (e, m) -> - Strong_emphasis ({ e with inline = normalize ~ext e.inline }, m) - | Inlines (i :: is, m) -> ( - let rec loop acc = function - | Inlines (is', _) :: is -> - loop acc (List.rev_append (List.rev is') is) - | (Text (t', _) as i') :: is -> ( - match acc with - | Text (t, _) :: acc -> - let i = Text (t ^ t', ()) in - loop (i :: acc) is - | _ -> loop (normalize ~ext i' :: acc) is) - | i :: is -> loop (normalize ~ext i :: acc) is - | [] -> List.rev acc - in - let is = loop [ normalize ~ext i ] is in - match is with [ i ] -> i | _ -> Inlines (is, m)) - | Ext_strikethrough (i, m) -> Ext_strikethrough (normalize ~ext i, m) - | i -> ext i - - let ext_none = ext_none - let to_plain_text ?(ext = ext_none) ~break_on_soft i = - let push s acc = (s :: List.hd acc) :: List.tl acc in - let newline acc = [] :: List.rev (List.hd acc) :: List.tl acc in - let rec loop ~break_on_soft acc = function - | Autolink (a, _) :: is -> - let acc = push (String.concat "" [ "<"; fst a.link; ">" ]) acc in - loop ~break_on_soft acc is - | Break ({ type' = `Hard; _ }, _) :: is -> - loop ~break_on_soft (newline acc) is - | Break ({ type' = `Soft; _ }, _) :: is -> - let acc = if break_on_soft then newline acc else push " " acc in - loop ~break_on_soft acc is - | Code_span (cs, _) :: is -> - loop ~break_on_soft (push (Code_span.code cs) acc) is - | Emphasis ({ inline; _ }, _) :: is - | Strong_emphasis ({ inline; _ }, _) :: is -> - loop ~break_on_soft acc (inline :: is) - | Inlines (is', _) :: is -> - loop ~break_on_soft acc (List.rev_append (List.rev is') is) - | Link (l, _) :: is | Image (l, _) :: is -> - loop ~break_on_soft acc (l.text :: is) - | Raw_html _ :: is -> loop ~break_on_soft acc is - | Text (t, _) :: is -> loop ~break_on_soft (push t acc) is - | Ext_strikethrough (i, _) :: is -> loop ~break_on_soft acc (i :: is) - | Ext_math_span (m, _) :: is -> - loop ~break_on_soft (push (Math_span.tex m) acc) is - | i :: is -> loop ~break_on_soft acc (ext ~break_on_soft i :: is) - | [] -> List.rev (List.rev (List.hd acc) :: List.tl acc) - in - loop ~break_on_soft ([] :: []) [ i ] - - let id ?buf ?ext i = - let text = to_plain_text ?ext ~break_on_soft:false i in - let s = String.concat "\n" (List.map (String.concat "") text) in - let b = - match buf with - | Some b -> - Buffer.reset b; - b - | None -> Buffer.create 256 - in - let[@inline] collapse_blanks b ~prev_byte = - (* Collapses non initial white *) - if Ascii.is_blank prev_byte && Buffer.length b <> 0 then - Buffer.add_char b '-' - in - let rec loop b s max ~prev_byte k = - if k > max then Buffer.contents b - else - match s.[k] with - | (' ' | '\t') as prev_byte -> loop b s max ~prev_byte (k + 1) - | ('_' | '-') as c -> - collapse_blanks b ~prev_byte; - Buffer.add_char b c; - loop b s max ~prev_byte:c (k + 1) - | _ -> - let () = collapse_blanks b ~prev_byte in - let d = String.get_utf_8_uchar s k in - let u = Uchar.utf_decode_uchar d in - let u = match Uchar.to_int u with 0x0000 -> Uchar.rep | _ -> u in - let k' = k + Uchar.utf_decode_length d in - if Cmarkit_data.is_unicode_punctuation u then - loop b s max ~prev_byte:'\x00' k' - else - let () = - match Cmarkit_data.unicode_case_fold u with - | None -> Buffer.add_utf_8_uchar b u - | Some fold -> Buffer.add_string b fold - in - let prev_byte = s.[k] in - loop b s max ~prev_byte k' - in - loop b s (String.length s - 1) ~prev_byte:'\x00' 0 + type t = + | Break + | Code_span of string list + | Emphasis of t + | Image of link + | Inlines of t list + | Link of link + | Raw_html of string list + | Strong_emphasis of t + | Text of string + and link = { text : t; reference : Link_definition.t } + + let is_empty = function Text "" | Inlines [] -> true | _ -> false end module Block = struct - type t = .. - - module Blank_line = struct - type t = Layout.blanks - end - - module Block_quote = struct - type nonrec t = { indent : Layout.indent; block : t } - let make ?(indent = 0) block = { indent; block } - let indent bq = bq.indent - let block bq = bq.block - end - - module Code_block = struct - type fenced_layout = { - indent : Layout.indent; - opening_fence : Layout.string node; - closing_fence : Layout.string node option; - } - - let default_fenced_layout = - { - indent = 0; - opening_fence = Layout.empty; - closing_fence = Some Layout.empty; - } - - type layout = [ `Indented | `Fenced of fenced_layout ] - type t = { - layout : layout; - info_string : string node option; - code : string node list; - } - - let make ?(layout = `Fenced default_fenced_layout) ?info_string code = - let layout = - match (info_string, layout) with - | Some _, `Indented -> `Fenced default_fenced_layout - | _, layout -> layout - in - { layout; info_string; code } - - let layout cb = cb.layout - let info_string cb = cb.info_string - let code cb = cb.code - - let make_fence cb = - let rec loop char counts = function - | [] -> counts - | (c, _) :: cs -> - let max = String.length c - 1 in - let k = ref 0 in - while !k <= max && c.[!k] = char do - incr k - done; - loop char (if !k <> 0 then !k :: counts else counts) cs - in - let char = - match cb.info_string with - | Some (i, _) when String.exists (Char.equal '`') i -> '~' - | None | Some _ -> '`' - in - let counts = loop char [] cb.code in - ( char, - Inline.Code_span.min_backtick_count (* not char specific *) - ~min:3 counts ) - - let language_of_info_string s = - let rec next_white s max i = - if i > max || Ascii.is_white s.[i] then i else next_white s max (i + 1) - in - if s = "" then None - else - let max = String.length s - 1 in - let white = next_white s max 0 in - let rem_first = Match.first_non_blank s ~last:max ~start:white in - let lang = String.sub s 0 white in - if lang = "" then None - else Some (lang, String.sub s rem_first (max - rem_first + 1)) - - let is_math_block = function - | None -> false - | Some (i, _) -> ( - match language_of_info_string i with - | Some ("math", _) -> true - | Some _ | None -> false) - end - - module Heading = struct - type atx_layout = { - indent : Layout.indent; - after_opening : Layout.blanks; - closing : Layout.string; - } - - let default_atx_layout = { indent = 0; after_opening = ""; closing = "" } - - type setext_layout = { - leading_indent : Layout.indent; - trailing_blanks : Layout.blanks; - underline_indent : Layout.indent; - underline_count : Layout.count node; - underline_blanks : Layout.blanks; - } - - type layout = [ `Atx of atx_layout | `Setext of setext_layout ] - type id = [ `Auto of string | `Id of string ] - type t = { layout : layout; level : int; inline : Inline.t; id : id option } - - let make ?id ?(layout = `Atx default_atx_layout) ~level inline = - let max = match layout with `Atx _ -> 6 | `Setext _ -> 2 in - let level = Int.max 1 (Int.min level max) in - { layout; level; inline; id } - - let layout h = h.layout - let level h = h.level - let inline h = h.inline - let id h = h.id - end - - module Html_block = struct - type t = string node list - end - - module List_item = struct - type block = t - type t = { - before_marker : Layout.indent; - marker : Layout.string node; - after_marker : Layout.indent; - block : block; - ext_task_marker : Uchar.t node option; - } - - let make ?(before_marker = 0) ?(marker = Layout.empty) ?(after_marker = 1) - ?ext_task_marker block = - { before_marker; marker; after_marker; block; ext_task_marker } - - let block i = i.block - let before_marker i = i.before_marker - let marker i = i.marker - let after_marker i = i.after_marker - let ext_task_marker i = i.ext_task_marker - let task_status_of_task_marker u = - match Uchar.to_int u with - | 0x0020 -> `Unchecked - | 0x0078 (* x *) - | 0x0058 (* X *) - | 0x2713 (* ✓ *) - | 0x2714 (* ✔ *) - | 0x10102 (* 𐄂 *) - | 0x1F5F8 (* 🗸*) -> - `Checked - | 0x007E (* ~ *) -> `Cancelled - | _ -> `Other u - end - - module List' = struct - type type' = [ `Unordered of Layout.char | `Ordered of int * Layout.char ] - type t = { type' : type'; tight : bool; items : List_item.t node list } - - let make ?(tight = true) type' items = { type'; tight; items } - - let type' l = l.type' - let tight l = l.tight - let items l = l.items - end - - module Paragraph = struct - type t = { - leading_indent : Layout.indent; - inline : Inline.t; - trailing_blanks : Layout.blanks; - } - - let make ?(leading_indent = 0) ?(trailing_blanks = "") inline = - { leading_indent; inline; trailing_blanks } - - let inline p = p.inline - let leading_indent p = p.leading_indent - let trailing_blanks p = p.trailing_blanks - end - - module Thematic_break = struct - type t = { indent : Layout.indent; layout : Layout.string } - let make ?(indent = 0) ?(layout = "---") () = { indent; layout } - let indent t = t.indent - let layout t = t.layout - end - - type t += - | Blank_line of Layout.blanks node - | Block_quote of Block_quote.t node - | Blocks of t list node - | Code_block of Code_block.t node - | Heading of Heading.t node - | Html_block of Html_block.t node - | Link_reference_definition of Link_definition.t node - | List of List'.t node - | Paragraph of Paragraph.t node - | Thematic_break of Thematic_break.t node - - let empty = Blocks ([], Meta.none) + type code_block = { info_string : string option; code : string list } + type list_type = Unordered | Ordered + + type id = [ `Auto of string | `Id of string ] + type heading = { level : int; inline : Inline.t; id : id option } + + type t = + | Blank_line + | Blocks of t list + | Code_block of code_block + | Heading of heading + | Html_block of string list + | Link_reference_definition of Link_definition.t + | List of list' + | Paragraph of Inline.t + and list' = { type_ : list_type; tight : bool; items : t list } + let empty = Blocks [] (* Extensions *) module Table = struct type align = [ `Left | `Center | `Right ] - type sep = align option * Layout.count - type cell_layout = Layout.blanks * Layout.blanks + type sep = align option type row = - [ `Header of (Inline.t * cell_layout) list - | `Sep of sep node list - | `Data of (Inline.t * cell_layout) list ] + [ `Header of Inline.t list | `Sep of sep list | `Data of Inline.t list ] - type t = { - indent : Layout.indent; - col_count : int; - rows : (row node * Layout.blanks) list; - } + type t = { col_count : int; rows : row list } let col_count rows = let rec loop c = function - | (((`Header cols | `Data cols), _), _) :: rs -> + | (`Header cols | `Data cols) :: rs -> loop (Int.max (List.length cols) c) rs - | ((`Sep cols, _), _) :: rs -> loop (Int.max (List.length cols) c) rs + | `Sep cols :: rs -> loop (Int.max (List.length cols) c) rs | [] -> c in loop 0 rows - let make ?(indent = 0) rows = { indent; col_count = col_count rows; rows } - let indent t = t.indent + let make rows = { col_count = col_count rows; rows } let col_count t = t.col_count let rows t = t.rows let parse_sep_row cs = let rec loop acc = function | [] -> Some (List.rev acc) - | (Inline.Text (s, meta), ("", "")) :: cs -> ( + | (Inline.Text s, ("", "")) :: cs -> ( if s = "" then None else let max = String.length s - 1 in @@ -919,125 +329,14 @@ module Block = struct | true, false -> Some `Left | false, true -> Some `Right in - loop (((sep, count), meta) :: acc) cs) + loop ((sep, count) :: acc) cs) | _ -> None in loop [] cs end - - module Footnote = struct - type nonrec t = { - indent : Layout.indent; - label : Label.t; - defined_label : Label.t option; - block : t; - } - - let make ?(indent = 0) ?defined_label:d label block = - let defined_label = match d with None -> Some label | Some d -> d in - { indent; label; defined_label; block } - - let indent fn = fn.indent - let label fn = fn.label - let defined_label fn = fn.defined_label - let block fn = fn.block - - type Label.def += Def of t node - let stub label defined_label = - Def ({ indent = 0; label; defined_label; block = empty }, Meta.none) - end - - type t += - | Ext_math_block of Code_block.t node - | Ext_table of Table.t node - | Ext_footnote_definition of Footnote.t node - - (* Functions on blocks *) - - let err_unknown = "Unknown Cmarkit.Block.t type extension" - - let ext_none _ = invalid_arg err_unknown - let meta ?(ext = ext_none) = function - | Blank_line (_, m) - | Block_quote (_, m) - | Blocks (_, m) - | Code_block (_, m) - | Heading (_, m) - | Html_block (_, m) - | Link_reference_definition (_, m) - | List (_, m) - | Paragraph (_, m) - | Thematic_break (_, m) - | Ext_math_block (_, m) - | Ext_table (_, m) - | Ext_footnote_definition (_, m) -> - m - | b -> ext b - - let rec normalize ?(ext = ext_none) = function - | ( Blank_line _ | Code_block _ | Heading _ | Html_block _ - | Link_reference_definition _ | Paragraph _ | Thematic_break _ - | Blocks ([], _) - | Ext_math_block _ | Ext_table _ ) as b -> - b - | Block_quote (b, m) -> - let b = { b with block = normalize ~ext b.block } in - Block_quote (b, m) - | List (l, m) -> - let item (i, meta) = - let block = List_item.block i in - ({ i with List_item.block = normalize ~ext block }, meta) - in - List ({ l with items = List.map item l.items }, m) - | Blocks (b :: bs, m) -> ( - let rec loop acc = function - | Blocks (bs', _) :: bs -> - loop acc (List.rev_append (List.rev bs') bs) - | b :: bs -> loop (normalize ~ext b :: acc) bs - | [] -> List.rev acc - in - let bs = loop [ normalize ~ext b ] bs in - match bs with [ b ] -> b | _ -> Blocks (bs, m)) - | Ext_footnote_definition (fn, m) -> - let fn = { fn with block = normalize ~ext fn.block } in - Ext_footnote_definition (fn, m) - | b -> ext b - - let rec defs ?(ext = fun _b _defs -> invalid_arg err_unknown) - ?(init = Label.Map.empty) = function - | Blank_line _ | Code_block _ | Heading _ | Html_block _ | Paragraph _ - | Thematic_break _ | Ext_math_block _ | Ext_table _ -> - init - | Block_quote (b, _) -> defs ~ext ~init (Block_quote.block b) - | Blocks (bs, _) -> List.fold_left (fun init b -> defs ~ext ~init b) init bs - | List (l, _) -> - let add init (i, _) = defs ~ext ~init (List_item.block i) in - List.fold_left add init l.items - | Link_reference_definition ld -> ( - match Link_definition.defined_label (fst ld) with - | None -> init - | Some def -> - Label.Map.add (Label.key def) (Link_definition.Def ld) init) - | Ext_footnote_definition fn -> - let init = - match Footnote.defined_label (fst fn) with - | None -> init - | Some def -> Label.Map.add (Label.key def) (Footnote.Def fn) init - in - defs ~ext ~init (Footnote.block (fst fn)) - | b -> ext init b end -module Doc = struct - type t = { nl : Layout.string; block : Block.t; defs : Label.defs } - let make ?(nl = "\n") ?(defs = Label.Map.empty) block = { nl; block; defs } - let empty = make (Block.Blocks ([], Meta.none)) - let nl d = d.nl - let block d = d.block - let defs d = d.defs - let unicode_version = Data_uchar.unicode_version - let commonmark_version = "0.30" -end +type doc = Block.t (* Heterogeneous dictionaries *) @@ -1090,54 +389,21 @@ module Dict = struct end type t = { - init_context : context -> Doc.t -> unit; + init_context : context -> doc -> unit; inline : inline; block : block; - doc : doc; } -and context = { - renderer : t; - mutable state : Dict.t; - b : Buffer.t; - mutable document : Doc.t; -} - -and inline = context -> Inline.t -> bool -and block = context -> Block.t -> bool -and doc = context -> Doc.t -> bool - -let nop _ _ = () -let none _ _ = false - -let make ?(init_context = nop) ?(inline = none) ?(block = none) ?(doc = none) () - = - { init_context; inline; block; doc } - -let compose g f = - let init_context c d = - g.init_context c d; - f.init_context c d - in - let block c b = f.block c b || g.block c b in - let inline c i = f.inline c i || g.inline c i in - let doc c d = f.doc c d || g.doc c d in - { init_context; inline; block; doc } +and context = { renderer : t; mutable state : Dict.t; b : Buffer.t } -let _init_context r = r.init_context -let _inline r = r.inline -let _block r = r.block -let _doc r = r.doc +and inline = context -> Inline.t -> unit +and block = context -> Block.t -> unit module Context = struct type t = context - let make renderer b = - { renderer; b; state = Dict.empty; document = Doc.empty } + let make renderer b = { renderer; b; state = Dict.empty } let buffer c = c.b - let renderer c = c.renderer - let get_document (c : context) = c.document - let get_defs (c : context) = Doc.defs c.document module State = struct type 'a t = 'a Dict.key @@ -1151,28 +417,16 @@ module Context = struct let init c d = c.renderer.init_context c d - let invalid_inline _ = invalid_arg "Unknown Inline.t case" - let invalid_block _ = invalid_arg "Unknown Block.t case" - let unhandled_doc _ = invalid_arg "Unhandled Doc.t" - let byte r c = Buffer.add_char r.b c let utf_8_uchar r u = Buffer.add_utf_8_uchar r.b u let string c s = Buffer.add_string c.b s - let inline c i = ignore (c.renderer.inline c i || invalid_inline i) - let block c b = ignore (c.renderer.block c b || invalid_block b) + let inline c i = c.renderer.inline c i + let block c b = c.renderer.block c b let doc (c : context) d = - c.document <- d; init c d; - ignore (c.renderer.doc c d || unhandled_doc d); - c.document <- Doc.empty + c.renderer.block c d end -let doc_to_string r d = - let b = Buffer.create 1024 in - let c = Context.make r b in - Context.doc c d; - Buffer.contents b - let buffer_add_doc r b d = Context.doc (Context.make r b) d type indent = @@ -1181,6 +435,7 @@ type indent = | `Q of int | `Fn of int * Label.t ] +(* TODO: Can we kill the state? *) type state = { nl : string; (* newline to output. *) mutable sot : bool; (* start of text *) @@ -1189,12 +444,11 @@ type state = { let state : state Context.State.t = Context.State.make () let get_state c = Context.State.get c state -let init_context c d = - Context.State.set c state (Some { nl = Doc.nl d; sot = true; indents = [] }) +let init_context c _d = + Context.State.set c state (Some { nl = "\n"; sot = true; indents = [] }) module Char_set = Set.Make (Char) -let esc_angles = Char_set.of_list [ '<'; '>' ] let esc_parens = Char_set.of_list [ '('; ')' ] let esc_quote = Char_set.singleton '\'' let esc_dquote = Char_set.singleton '\"' @@ -1304,9 +558,6 @@ let buffer_add_escaped_text b s = let escaped_text c s = buffer_add_escaped_text (Context.buffer c) s -let string_node_option c = function - | None -> () - | Some (s, _) -> Context.string c s let nchars c n char = for _i = 1 to n do Context.byte c char @@ -1366,7 +617,7 @@ and link_label_lines c lines = escaped_tight_block_lines c esc_link_label lines and escaped_tight_block_lines c cs = function | [] -> () | l :: ls -> - let tight c (blanks, (l, _)) = + let tight c blanks = Context.string c blanks; escaped_string c cs l in @@ -1379,65 +630,34 @@ and escaped_tight_block_lines c cs = function List.iter (line c) ls let block_lines c = function - | [] -> () - | (l, _) :: ls -> - let line c (l, _) = - newline c; - indent c; - Context.string c l - in - Context.string c l; - List.iter (line c) ls - -let tight_block_lines c = function | [] -> () | l :: ls -> - let tight c (blanks, (l, _)) = - Context.string c blanks; - Context.string c l - in let line c l = newline c; indent c; - tight c l + Context.string c l in - tight c l; + Context.string c l; List.iter (line c) ls -let autolink c a = - Context.byte c '<'; - Context.string c (fst (Inline.Autolink.link a)); - Context.byte c '>' - -let break c b = - let layout_before = fst (Inline.Break.layout_before b) in - let layout_after = fst (Inline.Break.layout_after b) in - let before, after = - match Inline.Break.type' b with - | `Soft -> (layout_before, layout_after) - | `Hard -> - ((if layout_before = "" then " " else layout_before), layout_after) - in - Context.string c before; +let break c = + Context.string c " "; newline c; - indent c; - Context.string c after + indent c let code_span c cs = - nchars c (Inline.Code_span.backtick_count cs) '`'; - tight_block_lines c (Inline.Code_span.code_layout cs); - nchars c (Inline.Code_span.backtick_count cs) '`' + nchars c 1 '`'; + List.iter (Context.string c) cs; + nchars c 1 '`' -let emphasis c e = - let delim = Inline.Emphasis.delim e and i = Inline.Emphasis.inline e in - let delim = if not (delim = '*' || delim = '_') then '*' else delim in +let emphasis c i = + let delim = '*' in Context.byte c delim; Context.inline c i; Context.byte c delim -let strong_emphasis c e = - let delim = Inline.Emphasis.delim e and i = Inline.Emphasis.inline e in - let delim = if not (delim = '*' || delim = '_') then '*' else delim in +let strong_emphasis c i = + let delim = '*' in Context.byte c delim; Context.byte c delim; Context.inline c i; @@ -1460,182 +680,77 @@ let link_title c open_delim title = Context.byte c close let link_definition c ld = - let layout = Link_definition.layout ld in - block_lines c layout.before_dest; (match Link_definition.dest ld with | None -> () - | Some (dest, _) -> - if layout.angled_dest then ( - Context.byte c '<'; - escaped_string c esc_angles dest; - Context.byte c '>') - else escaped_string c esc_parens dest); + | Some dest -> escaped_string c esc_parens dest); if - layout.after_dest = [] - && Option.is_some (Link_definition.dest ld) + Option.is_some (Link_definition.dest ld) && Option.is_some (Link_definition.title ld) then Context.byte c ' ' (* at least a space is needed *); - block_lines c layout.after_dest; - link_title c layout.title_open_delim (Link_definition.title ld); - block_lines c layout.after_title - -let link c l = - match Inline.Link.reference l with - | `Inline (ld, _) -> - Context.byte c '['; - Context.inline c (Inline.Link.text l); - Context.byte c ']'; - Context.byte c '('; - link_definition c ld; - Context.byte c ')' - | `Ref (`Shortcut, label, _) -> - Context.byte c '['; - link_label_lines c (Label.text label); - Context.byte c ']' - | `Ref (`Collapsed, label, _) -> - Context.byte c '['; - link_label_lines c (Label.text label); - Context.byte c ']'; - Context.string c "[]" - | `Ref (`Full, label, _) -> - Context.byte c '['; - Context.inline c (Inline.Link.text l); - Context.byte c ']'; - Context.byte c '['; - link_label_lines c (Label.text label); - Context.byte c ']' - -let inlines c is = List.iter (Context.inline c) is + link_title c '\"' (Link_definition.title ld) + +let link c (l : Inline.link) = + Context.byte c '['; + Context.inline c l.text; + Context.byte c ']'; + Context.byte c '('; + link_definition c l.reference; + Context.byte c ')' + let image c l = Context.byte c '!'; link c l -let raw_html c h = tight_block_lines c h +let raw_html c h = List.iter (Context.string c) h let text c t = escaped_text c t -let strikethrough c s = - let i = Inline.Strikethrough.inline s in - Context.string c "~~"; - Context.inline c i; - Context.string c "~~" - -let math_span c ms = - let sep = if Inline.Math_span.display ms then "$$" else "$" in - Context.string c sep; - tight_block_lines c (Inline.Math_span.tex_layout ms); - Context.string c sep - let inline c = function - | Inline.Autolink (a, _) -> - autolink c a; - true - | Inline.Break (b, _) -> - break c b; - true - | Inline.Code_span (cs, _) -> - code_span c cs; - true - | Inline.Emphasis (e, _) -> - emphasis c e; - true - | Inline.Image (i, _) -> - image c i; - true - | Inline.Inlines (is, _) -> - inlines c is; - true - | Inline.Link (l, _) -> - link c l; - true - | Inline.Raw_html (html, _) -> - raw_html c html; - true - | Inline.Strong_emphasis (e, _) -> - strong_emphasis c e; - true - | Inline.Text (t, _) -> - text c t; - true - | Inline.Ext_strikethrough (s, _) -> - strikethrough c s; - true - | Inline.Ext_math_span (m, _) -> - math_span c m; - true - | _ -> - Context.string c ""; - true + | Inline.Break -> break c + | Inline.Code_span cs -> code_span c cs + | Inline.Emphasis e -> emphasis c e + | Inline.Image i -> image c i + | Inline.Inlines is -> List.iter (Context.inline c) is + | Inline.Link l -> link c l + | Inline.Raw_html html -> raw_html c html + | Inline.Strong_emphasis e -> strong_emphasis c e + | Inline.Text t -> text c t let blank_line c l = newline c; indent c; Context.string c l -let block_quote c bq = - push_indent c (`Q (Block.Block_quote.indent bq)); - Context.block c (Block.Block_quote.block bq); - pop_indent c +let string_node_option c = function None -> () | Some s -> Context.string c s -let code_block c cb = - match Block.Code_block.layout cb with - | `Indented -> - newline c; - push_indent c (`I 4); - indent c; - block_lines c (Block.Code_block.code cb); - pop_indent c - | `Fenced f -> - let opening, closing = - match fst f.opening_fence with - | "" -> - let char, len = Block.Code_block.make_fence cb in - let f = String.make len char in - (f, Some f) - | opening -> (opening, Option.map fst f.closing_fence) - in - let info_string = Block.Code_block.info_string cb in - let code = Block.Code_block.code cb in - newline c; - push_indent c (`I f.indent); - indent c; - Context.string c opening; - string_node_option c info_string; - if code <> [] then ( - newline c; - indent c; - block_lines c code); - (match closing with - | None -> () - | Some close -> - newline c; - indent c; - Context.string c close); - pop_indent c - -let heading c h = +let code_block c (cb : Block.code_block) = + let opening, closing = + let char, len = ('`', 3) in + let f = String.make len char in + (f, Some f) + in + let info_string = cb.info_string in + let code = cb.code in newline c; + push_indent c (`I 0); indent c; - match Block.Heading.layout h with - | `Atx { indent; after_opening; closing } -> - let inline = Block.Heading.inline h in - nchars c indent ' '; - nchars c (Block.Heading.level h) '#'; - if after_opening = "" && not (Inline.is_empty inline) then - Context.byte c ' ' - else Context.string c after_opening; - Context.inline c inline; - Context.string c closing - | `Setext l -> - let u = - match Block.Heading.level h with 1 -> '=' | 2 -> '-' | _ -> '-' - in - nchars c l.leading_indent ' '; - Context.inline c (Block.Heading.inline h); - Context.string c l.trailing_blanks; + Context.string c opening; + string_node_option c info_string; + if code <> [] then ( + newline c; + indent c; + block_lines c code); + (match closing with + | None -> () + | Some close -> newline c; indent c; - nchars c l.underline_indent ' '; - nchars c (fst l.underline_count) u; - Context.string c l.underline_blanks + Context.string c close); + pop_indent c + +let heading c (h : Block.heading) = + newline c; + nchars c h.level '#'; + if not (Inline.is_empty h.inline) then Context.byte c ' ' else (); + Context.inline c h.inline let html_block c h = newline c; @@ -1645,7 +760,7 @@ let html_block c h = let link_reference_definition c ld = newline c; indent c; - nchars c (Link_definition.layout ld).indent ' '; + nchars c 0 ' '; Context.byte c '['; (match Link_definition.label ld with | None -> () @@ -1653,145 +768,54 @@ let link_reference_definition c ld = Context.string c "]:"; link_definition c ld -let unordered_item c marker (i, _) = - let before = Block.List_item.before_marker i in - let after = Block.List_item.after_marker i in - let task = Option.map fst (Block.List_item.ext_task_marker i) in +let unordered_item c marker i = + let before = 0 in + let after = 1 in + let task = None in push_indent c (`L (before, marker, after, task)); - Context.block c (Block.List_item.block i); + Context.block c i; pop_indent c -let ordered_item c sep num (i, _) = - let before = Block.List_item.before_marker i in - let marker = fst (Block.List_item.marker i) in - let marker = if marker = "" then Int.to_string num ^ sep else marker in - let after = Block.List_item.after_marker i in - let task = Option.map fst (Block.List_item.ext_task_marker i) in +let ordered_item c num i = + let before = 0 in + let marker = Int.to_string num ^ "." in + let after = 1 in + let task = None in push_indent c (`L (before, marker, after, task)); - Context.block c (Block.List_item.block i); + Context.block c i; pop_indent c; num + 1 -let list c l = - match Block.List'.type' l with - | `Unordered marker -> - let marker = match marker with '*' | '-' | '+' -> marker | _ -> '*' in - let marker = String.make 1 marker in - List.iter (unordered_item c marker) (Block.List'.items l) - | `Ordered (start, sep) -> - let sep = if sep <> '.' && sep <> ')' then '.' else sep in - let sep = String.make 1 sep in - ignore (List.fold_left (ordered_item c sep) start (Block.List'.items l)) +let list c (l : Block.list') = + match l.type_ with + | Unordered -> + let marker = String.make 1 '-' in + List.iter (unordered_item c marker) l.items + | Ordered -> + let start = 1 in + ignore (List.fold_left (ordered_item c) start l.items) let paragraph c p = newline c; indent c; - nchars c (Block.Paragraph.leading_indent p) ' '; - Context.inline c (Block.Paragraph.inline p); - Context.string c (Block.Paragraph.trailing_blanks p) - -let thematic_break c t = - let ind = Block.Thematic_break.indent t in - let break = Block.Thematic_break.layout t in - let break = if break = "" then "---" else break in - newline c; - indent c; - nchars c ind ' '; - Context.string c break - -let table c t = - let col c (i, (before, after)) = - Context.byte c '|'; - Context.string c before; - Context.inline c i; - Context.string c after - in - let sep c ((align, len), _) = - Context.byte c '|'; - match align with - | None -> nchars c len '-' - | Some `Left -> - Context.byte c ':'; - nchars c len '-' - | Some `Center -> - Context.byte c ':'; - nchars c len '-'; - Context.byte c ':' - | Some `Right -> - nchars c len '-'; - Context.byte c ':' - in - let row c = function - | (`Header cols, _), blanks | (`Data cols, _), blanks -> - newline c; - indent c; - if cols = [] then Context.byte c '|' else List.iter (col c) cols; - Context.byte c '|'; - Context.string c blanks - | (`Sep seps, _), blanks -> - newline c; - indent c; - if seps = [] then Context.byte c '|' else List.iter (sep c) seps; - Context.byte c '|'; - Context.string c blanks - in - push_indent c (`I (Block.Table.indent t)); - List.iter (row c) (Block.Table.rows t); - pop_indent c - -let footnote c fn = - push_indent c (`Fn (Block.Footnote.indent fn, Block.Footnote.label fn)); - Context.block c (Block.Footnote.block fn); - pop_indent c - -let block c = function - | Block.Blank_line (l, _) -> - blank_line c l; - true - | Block.Block_quote (b, _) -> - block_quote c b; - true - | Block.Blocks (bs, _) -> - List.iter (Context.block c) bs; - true - | Block.Code_block (cb, _) -> - code_block c cb; - true - | Block.Heading (h, _) -> - heading c h; - true - | Block.Html_block (h, _) -> - html_block c h; - true - | Block.Link_reference_definition (ld, _) -> - link_reference_definition c ld; - true - | Block.List (l, _) -> - list c l; - true - | Block.Paragraph (p, _) -> - paragraph c p; - true - | Block.Thematic_break (t, _) -> - thematic_break c t; - true - | Block.Ext_math_block (cb, _) -> - code_block c cb; - true - | Block.Ext_table (t, _) -> - table c t; - true - | Block.Ext_footnote_definition (t, _) -> - footnote c t; - true - | _ -> - newline c; - indent c; - Context.string c ""; - true - -let doc c d = - Context.block c (Doc.block d); - true - -let renderer () = make ~init_context ~inline ~block ~doc () + nchars c 0 ' '; + Context.inline c p; + Context.string c "" + +let block c b = + match (b : Block.t) with + | Blank_line -> blank_line c "" + | Blocks bs -> List.iter (Context.block c) bs + | Code_block cb -> code_block c cb + | Heading h -> heading c h + | Html_block h -> html_block c h + | Link_reference_definition ld -> link_reference_definition c ld + | List l -> list c l + | Paragraph p -> paragraph c p + +let to_string d = + let t = { init_context; inline; block } in + let buffer = Buffer.create 1024 in + let c = Context.make t buffer in + Context.doc c d; + Buffer.contents buffer From fad3be094acee9c4efbeaca2118ccbf586b0303f Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 9 May 2025 12:44:53 +0200 Subject: [PATCH 39/53] Don't format uchar data --- src/markdown2/data_uchar.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/markdown2/data_uchar.ml b/src/markdown2/data_uchar.ml index ac10a5ec31..0f46a7e99a 100644 --- a/src/markdown2/data_uchar.ml +++ b/src/markdown2/data_uchar.ml @@ -113,7 +113,7 @@ let [@ocamlformat "disable"] punctuation = 0x1BC9F; 0x1DA87; 0x1DA88; 0x1DA89; 0x1DA8A; 0x1DA8B; 0x1E5FF; 0x1E95E; 0x1E95F|] -let case_fold = +let [@ocamlformat "disable"] case_fold = [|0x0041, "\u{0061}"; 0x0042, "\u{0062}"; 0x0043, "\u{0063}"; 0x0044, "\u{0064}"; 0x0045, "\u{0065}"; 0x0046, "\u{0066}"; 0x0047, "\u{0067}"; 0x0048, "\u{0068}"; 0x0049, "\u{0069}"; From c42bbed69382392b8a807cdc2695dc884124b8f7 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 9 May 2025 13:12:06 +0200 Subject: [PATCH 40/53] Simplify Render module --- src/markdown2/generator.ml | 3 +- src/markdown2/renderer.ml | 101 ++++++++++--------------------------- 2 files changed, 29 insertions(+), 75 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 8174b20448..8078af6431 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -1,10 +1,8 @@ open Odoc_utils -module HLink = Link module Types = Odoc_document.Types module Doctree = Odoc_document.Doctree module Url = Odoc_document.Url -module Link = HLink let source fn (t : Types.Source.t) = let rec token (x : Types.Source.token) = @@ -82,6 +80,7 @@ and inline ~(config : Config.t) ~resolve l = "Markdown only supports html blocks. There's a raw with " ^ another_lang in + (* QUESTION: Should we render an empty block? Can we do something else rather failwith? *) failwith msg) in List.concat_map one l diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index 6abc9597f4..3d98893a3c 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -178,44 +178,12 @@ module Block_line = struct let sub = String.sub s start (last - start + 1) in sub :: acc - (* let flush_tight s start last acc = - (* If [s] has newlines, blanks after newlines are layout *) - if start > last then "" :: acc - else - match acc with - | [] (* On the first line the blanks are legit *) -> - String.sub s start (last - start + 1) :: acc - | acc -> - let nb = Match.first_non_blank s ~last ~start in - String.sub s start (nb - 1 - start + 1) - :: String.sub s nb (last - nb + 1) - :: acc - *) - (* Block lines *) - - let to_string = fst let list_of_string s = _list_of_string flush s - (* Tight lines *) - type tight = string - - (* let tight_list_of_string s = _list_of_string flush_tight s *) - - (* Blank lines *) end -(* TODO: What's label? *) -module Label = struct - type key = string - type t = { key : key; text : Block_line.tight list } - let make ~key text = { key; text } - let key t = t.key - let text t = t.text - let text_to_string t = String.concat " " t.text - - let compare l0 l1 = String.compare l0.key l1.key -end +type label = { key : string; text : Block_line.tight list } module Link_definition = struct (* let default_layout = @@ -229,8 +197,8 @@ module Link_definition = struct } *) type t = { - label : Label.t option; - defined_label : Label.t option; + label : label option; + defined_label : label option; dest : string option; title : Block_line.tight list option; } @@ -427,25 +395,20 @@ module Context = struct c.renderer.block c d end -let buffer_add_doc r b d = Context.doc (Context.make r b) d - -type indent = - [ `I of int - | `L of int * string * int * Uchar.t option - | `Q of int - | `Fn of int * Label.t ] +type indent = [ `I of int | `L of int * string * int * Uchar.t option ] -(* TODO: Can we kill the state? *) type state = { - nl : string; (* newline to output. *) - mutable sot : bool; (* start of text *) - mutable indents : indent list; (* indentation stack. *) + newline_to_output : string; + mutable start_of_text : bool; + mutable identation_stack : indent list; } let state : state Context.State.t = Context.State.make () let get_state c = Context.State.get c state let init_context c _d = - Context.State.set c state (Some { nl = "\n"; sot = true; indents = [] }) + Context.State.set c state + (Some + { newline_to_output = "\n"; start_of_text = true; identation_stack = [] }) module Char_set = Set.Make (Char) @@ -565,15 +528,19 @@ let nchars c n char = let newline c = (* Block generally introduce newlines, except the first one. *) - let st = get_state c in - if st.sot then st.sot <- false else Context.string c st.nl + let state = get_state c in + if state.start_of_text then state.start_of_text <- false + else Context.string c state.newline_to_output let push_indent c n = - let st = get_state c in - st.indents <- n :: st.indents + let state = get_state c in + state.identation_stack <- n :: state.identation_stack + let pop_indent c = - let st = get_state c in - match st.indents with [] -> () | ns -> st.indents <- List.tl ns + let state = get_state c in + match state.identation_stack with + | [] -> () + | ns -> state.identation_stack <- List.tl ns let rec indent c = let rec loop c acc = function @@ -581,11 +548,6 @@ let rec indent c = | (`I n as i) :: is -> nchars c n ' '; loop c (i :: acc) is - | (`Q n as i) :: is -> - nchars c n ' '; - Context.byte c '>'; - Context.byte c ' '; - loop c (i :: acc) is | `L (before, m, after, task) :: is -> nchars c before ' '; Context.string c m; @@ -601,16 +563,10 @@ let rec indent c = in (* On the next call we'll just indent for the list item *) loop c (`I (before + String.length m + after) :: acc) is - | `Fn (before, label) :: is -> - nchars c before ' '; - Context.byte c '['; - link_label_lines c (Label.text label); - Context.string c "]:"; - (* On the next call we'll just indent to ^ for the footnote *) - loop c (`I (before + 1) :: acc) is + | _ -> [] in - let st = get_state c in - st.indents <- loop c [] (List.rev st.indents) + let state = get_state c in + state.identation_stack <- loop c [] (List.rev state.identation_stack) and link_label_lines c lines = escaped_tight_block_lines c esc_link_label lines @@ -700,19 +656,18 @@ let link c (l : Inline.link) = let image c l = Context.byte c '!'; link c l -let raw_html c h = List.iter (Context.string c) h let text c t = escaped_text c t let inline c = function + | Inline.Text t -> text c t + | Inline.Link l -> link c l | Inline.Break -> break c - | Inline.Code_span cs -> code_span c cs | Inline.Emphasis e -> emphasis c e + | Inline.Code_span cs -> code_span c cs | Inline.Image i -> image c i | Inline.Inlines is -> List.iter (Context.inline c) is - | Inline.Link l -> link c l - | Inline.Raw_html html -> raw_html c html | Inline.Strong_emphasis e -> strong_emphasis c e - | Inline.Text t -> text c t + | Inline.Raw_html html -> List.iter (Context.string c) html let blank_line c l = newline c; @@ -764,7 +719,7 @@ let link_reference_definition c ld = Context.byte c '['; (match Link_definition.label ld with | None -> () - | Some label -> escaped_tight_block_lines c esc_link_label (Label.text label)); + | Some label -> escaped_tight_block_lines c esc_link_label label.text); Context.string c "]:"; link_definition c ld From fe94b56a0a409dfcab4dd1fe03ee63c81b47656b Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 9 May 2025 14:38:44 +0200 Subject: [PATCH 41/53] Simplify Render module --- src/markdown2/data_uchar.ml | 652 ------------------------------------ src/markdown2/generator.ml | 24 +- src/markdown2/renderer.ml | 368 +++++++------------- 3 files changed, 128 insertions(+), 916 deletions(-) delete mode 100644 src/markdown2/data_uchar.ml diff --git a/src/markdown2/data_uchar.ml b/src/markdown2/data_uchar.ml deleted file mode 100644 index 0f46a7e99a..0000000000 --- a/src/markdown2/data_uchar.ml +++ /dev/null @@ -1,652 +0,0 @@ -(*--------------------------------------------------------------------------- - Copyright (c) 2024 The cmarkit programmers. All rights reserved. - SPDX-License-Identifier: ISC - ---------------------------------------------------------------------------*) - - -let unicode_version = "16.0.0" - -let [@ocamlformat "disable"] whitespace = - [|0x0009; 0x000A; 0x000C; 0x000D; 0x0020; 0x00A0; 0x1680; 0x2000; 0x2001; - 0x2002; 0x2003; 0x2004; 0x2005; 0x2006; 0x2007; 0x2008; 0x2009; 0x200A; - 0x202F; 0x205F; 0x3000|] - -let [@ocamlformat "disable"] punctuation = - [|0x0021; 0x0022; 0x0023; 0x0024; 0x0025; 0x0026; 0x0027; 0x0028; 0x0029; - 0x002A; 0x002B; 0x002C; 0x002D; 0x002E; 0x002F; 0x003A; 0x003B; 0x003C; - 0x003D; 0x003E; 0x003F; 0x0040; 0x005B; 0x005C; 0x005D; 0x005E; 0x005F; - 0x0060; 0x007B; 0x007C; 0x007D; 0x007E; 0x00A1; 0x00A7; 0x00AB; 0x00B6; - 0x00B7; 0x00BB; 0x00BF; 0x037E; 0x0387; 0x055A; 0x055B; 0x055C; 0x055D; - 0x055E; 0x055F; 0x0589; 0x058A; 0x05BE; 0x05C0; 0x05C3; 0x05C6; 0x05F3; - 0x05F4; 0x0609; 0x060A; 0x060C; 0x060D; 0x061B; 0x061D; 0x061E; 0x061F; - 0x066A; 0x066B; 0x066C; 0x066D; 0x06D4; 0x0700; 0x0701; 0x0702; 0x0703; - 0x0704; 0x0705; 0x0706; 0x0707; 0x0708; 0x0709; 0x070A; 0x070B; 0x070C; - 0x070D; 0x07F7; 0x07F8; 0x07F9; 0x0830; 0x0831; 0x0832; 0x0833; 0x0834; - 0x0835; 0x0836; 0x0837; 0x0838; 0x0839; 0x083A; 0x083B; 0x083C; 0x083D; - 0x083E; 0x085E; 0x0964; 0x0965; 0x0970; 0x09FD; 0x0A76; 0x0AF0; 0x0C77; - 0x0C84; 0x0DF4; 0x0E4F; 0x0E5A; 0x0E5B; 0x0F04; 0x0F05; 0x0F06; 0x0F07; - 0x0F08; 0x0F09; 0x0F0A; 0x0F0B; 0x0F0C; 0x0F0D; 0x0F0E; 0x0F0F; 0x0F10; - 0x0F11; 0x0F12; 0x0F14; 0x0F3A; 0x0F3B; 0x0F3C; 0x0F3D; 0x0F85; 0x0FD0; - 0x0FD1; 0x0FD2; 0x0FD3; 0x0FD4; 0x0FD9; 0x0FDA; 0x104A; 0x104B; 0x104C; - 0x104D; 0x104E; 0x104F; 0x10FB; 0x1360; 0x1361; 0x1362; 0x1363; 0x1364; - 0x1365; 0x1366; 0x1367; 0x1368; 0x1400; 0x166E; 0x169B; 0x169C; 0x16EB; - 0x16EC; 0x16ED; 0x1735; 0x1736; 0x17D4; 0x17D5; 0x17D6; 0x17D8; 0x17D9; - 0x17DA; 0x1800; 0x1801; 0x1802; 0x1803; 0x1804; 0x1805; 0x1806; 0x1807; - 0x1808; 0x1809; 0x180A; 0x1944; 0x1945; 0x1A1E; 0x1A1F; 0x1AA0; 0x1AA1; - 0x1AA2; 0x1AA3; 0x1AA4; 0x1AA5; 0x1AA6; 0x1AA8; 0x1AA9; 0x1AAA; 0x1AAB; - 0x1AAC; 0x1AAD; 0x1B4E; 0x1B4F; 0x1B5A; 0x1B5B; 0x1B5C; 0x1B5D; 0x1B5E; - 0x1B5F; 0x1B60; 0x1B7D; 0x1B7E; 0x1B7F; 0x1BFC; 0x1BFD; 0x1BFE; 0x1BFF; - 0x1C3B; 0x1C3C; 0x1C3D; 0x1C3E; 0x1C3F; 0x1C7E; 0x1C7F; 0x1CC0; 0x1CC1; - 0x1CC2; 0x1CC3; 0x1CC4; 0x1CC5; 0x1CC6; 0x1CC7; 0x1CD3; 0x2010; 0x2011; - 0x2012; 0x2013; 0x2014; 0x2015; 0x2016; 0x2017; 0x2018; 0x2019; 0x201A; - 0x201B; 0x201C; 0x201D; 0x201E; 0x201F; 0x2020; 0x2021; 0x2022; 0x2023; - 0x2024; 0x2025; 0x2026; 0x2027; 0x2030; 0x2031; 0x2032; 0x2033; 0x2034; - 0x2035; 0x2036; 0x2037; 0x2038; 0x2039; 0x203A; 0x203B; 0x203C; 0x203D; - 0x203E; 0x203F; 0x2040; 0x2041; 0x2042; 0x2043; 0x2045; 0x2046; 0x2047; - 0x2048; 0x2049; 0x204A; 0x204B; 0x204C; 0x204D; 0x204E; 0x204F; 0x2050; - 0x2051; 0x2053; 0x2054; 0x2055; 0x2056; 0x2057; 0x2058; 0x2059; 0x205A; - 0x205B; 0x205C; 0x205D; 0x205E; 0x207D; 0x207E; 0x208D; 0x208E; 0x2308; - 0x2309; 0x230A; 0x230B; 0x2329; 0x232A; 0x2768; 0x2769; 0x276A; 0x276B; - 0x276C; 0x276D; 0x276E; 0x276F; 0x2770; 0x2771; 0x2772; 0x2773; 0x2774; - 0x2775; 0x27C5; 0x27C6; 0x27E6; 0x27E7; 0x27E8; 0x27E9; 0x27EA; 0x27EB; - 0x27EC; 0x27ED; 0x27EE; 0x27EF; 0x2983; 0x2984; 0x2985; 0x2986; 0x2987; - 0x2988; 0x2989; 0x298A; 0x298B; 0x298C; 0x298D; 0x298E; 0x298F; 0x2990; - 0x2991; 0x2992; 0x2993; 0x2994; 0x2995; 0x2996; 0x2997; 0x2998; 0x29D8; - 0x29D9; 0x29DA; 0x29DB; 0x29FC; 0x29FD; 0x2CF9; 0x2CFA; 0x2CFB; 0x2CFC; - 0x2CFE; 0x2CFF; 0x2D70; 0x2E00; 0x2E01; 0x2E02; 0x2E03; 0x2E04; 0x2E05; - 0x2E06; 0x2E07; 0x2E08; 0x2E09; 0x2E0A; 0x2E0B; 0x2E0C; 0x2E0D; 0x2E0E; - 0x2E0F; 0x2E10; 0x2E11; 0x2E12; 0x2E13; 0x2E14; 0x2E15; 0x2E16; 0x2E17; - 0x2E18; 0x2E19; 0x2E1A; 0x2E1B; 0x2E1C; 0x2E1D; 0x2E1E; 0x2E1F; 0x2E20; - 0x2E21; 0x2E22; 0x2E23; 0x2E24; 0x2E25; 0x2E26; 0x2E27; 0x2E28; 0x2E29; - 0x2E2A; 0x2E2B; 0x2E2C; 0x2E2D; 0x2E2E; 0x2E30; 0x2E31; 0x2E32; 0x2E33; - 0x2E34; 0x2E35; 0x2E36; 0x2E37; 0x2E38; 0x2E39; 0x2E3A; 0x2E3B; 0x2E3C; - 0x2E3D; 0x2E3E; 0x2E3F; 0x2E40; 0x2E41; 0x2E42; 0x2E43; 0x2E44; 0x2E45; - 0x2E46; 0x2E47; 0x2E48; 0x2E49; 0x2E4A; 0x2E4B; 0x2E4C; 0x2E4D; 0x2E4E; - 0x2E4F; 0x2E52; 0x2E53; 0x2E54; 0x2E55; 0x2E56; 0x2E57; 0x2E58; 0x2E59; - 0x2E5A; 0x2E5B; 0x2E5C; 0x2E5D; 0x3001; 0x3002; 0x3003; 0x3008; 0x3009; - 0x300A; 0x300B; 0x300C; 0x300D; 0x300E; 0x300F; 0x3010; 0x3011; 0x3014; - 0x3015; 0x3016; 0x3017; 0x3018; 0x3019; 0x301A; 0x301B; 0x301C; 0x301D; - 0x301E; 0x301F; 0x3030; 0x303D; 0x30A0; 0x30FB; 0xA4FE; 0xA4FF; 0xA60D; - 0xA60E; 0xA60F; 0xA673; 0xA67E; 0xA6F2; 0xA6F3; 0xA6F4; 0xA6F5; 0xA6F6; - 0xA6F7; 0xA874; 0xA875; 0xA876; 0xA877; 0xA8CE; 0xA8CF; 0xA8F8; 0xA8F9; - 0xA8FA; 0xA8FC; 0xA92E; 0xA92F; 0xA95F; 0xA9C1; 0xA9C2; 0xA9C3; 0xA9C4; - 0xA9C5; 0xA9C6; 0xA9C7; 0xA9C8; 0xA9C9; 0xA9CA; 0xA9CB; 0xA9CC; 0xA9CD; - 0xA9DE; 0xA9DF; 0xAA5C; 0xAA5D; 0xAA5E; 0xAA5F; 0xAADE; 0xAADF; 0xAAF0; - 0xAAF1; 0xABEB; 0xFD3E; 0xFD3F; 0xFE10; 0xFE11; 0xFE12; 0xFE13; 0xFE14; - 0xFE15; 0xFE16; 0xFE17; 0xFE18; 0xFE19; 0xFE30; 0xFE31; 0xFE32; 0xFE33; - 0xFE34; 0xFE35; 0xFE36; 0xFE37; 0xFE38; 0xFE39; 0xFE3A; 0xFE3B; 0xFE3C; - 0xFE3D; 0xFE3E; 0xFE3F; 0xFE40; 0xFE41; 0xFE42; 0xFE43; 0xFE44; 0xFE45; - 0xFE46; 0xFE47; 0xFE48; 0xFE49; 0xFE4A; 0xFE4B; 0xFE4C; 0xFE4D; 0xFE4E; - 0xFE4F; 0xFE50; 0xFE51; 0xFE52; 0xFE54; 0xFE55; 0xFE56; 0xFE57; 0xFE58; - 0xFE59; 0xFE5A; 0xFE5B; 0xFE5C; 0xFE5D; 0xFE5E; 0xFE5F; 0xFE60; 0xFE61; - 0xFE63; 0xFE68; 0xFE6A; 0xFE6B; 0xFF01; 0xFF02; 0xFF03; 0xFF05; 0xFF06; - 0xFF07; 0xFF08; 0xFF09; 0xFF0A; 0xFF0C; 0xFF0D; 0xFF0E; 0xFF0F; 0xFF1A; - 0xFF1B; 0xFF1F; 0xFF20; 0xFF3B; 0xFF3C; 0xFF3D; 0xFF3F; 0xFF5B; 0xFF5D; - 0xFF5F; 0xFF60; 0xFF61; 0xFF62; 0xFF63; 0xFF64; 0xFF65; 0x10100; 0x10101; - 0x10102; 0x1039F; 0x103D0; 0x1056F; 0x10857; 0x1091F; 0x1093F; 0x10A50; - 0x10A51; 0x10A52; 0x10A53; 0x10A54; 0x10A55; 0x10A56; 0x10A57; 0x10A58; - 0x10A7F; 0x10AF0; 0x10AF1; 0x10AF2; 0x10AF3; 0x10AF4; 0x10AF5; 0x10AF6; - 0x10B39; 0x10B3A; 0x10B3B; 0x10B3C; 0x10B3D; 0x10B3E; 0x10B3F; 0x10B99; - 0x10B9A; 0x10B9B; 0x10B9C; 0x10D6E; 0x10EAD; 0x10F55; 0x10F56; 0x10F57; - 0x10F58; 0x10F59; 0x10F86; 0x10F87; 0x10F88; 0x10F89; 0x11047; 0x11048; - 0x11049; 0x1104A; 0x1104B; 0x1104C; 0x1104D; 0x110BB; 0x110BC; 0x110BE; - 0x110BF; 0x110C0; 0x110C1; 0x11140; 0x11141; 0x11142; 0x11143; 0x11174; - 0x11175; 0x111C5; 0x111C6; 0x111C7; 0x111C8; 0x111CD; 0x111DB; 0x111DD; - 0x111DE; 0x111DF; 0x11238; 0x11239; 0x1123A; 0x1123B; 0x1123C; 0x1123D; - 0x112A9; 0x113D4; 0x113D5; 0x113D7; 0x113D8; 0x1144B; 0x1144C; 0x1144D; - 0x1144E; 0x1144F; 0x1145A; 0x1145B; 0x1145D; 0x114C6; 0x115C1; 0x115C2; - 0x115C3; 0x115C4; 0x115C5; 0x115C6; 0x115C7; 0x115C8; 0x115C9; 0x115CA; - 0x115CB; 0x115CC; 0x115CD; 0x115CE; 0x115CF; 0x115D0; 0x115D1; 0x115D2; - 0x115D3; 0x115D4; 0x115D5; 0x115D6; 0x115D7; 0x11641; 0x11642; 0x11643; - 0x11660; 0x11661; 0x11662; 0x11663; 0x11664; 0x11665; 0x11666; 0x11667; - 0x11668; 0x11669; 0x1166A; 0x1166B; 0x1166C; 0x116B9; 0x1173C; 0x1173D; - 0x1173E; 0x1183B; 0x11944; 0x11945; 0x11946; 0x119E2; 0x11A3F; 0x11A40; - 0x11A41; 0x11A42; 0x11A43; 0x11A44; 0x11A45; 0x11A46; 0x11A9A; 0x11A9B; - 0x11A9C; 0x11A9E; 0x11A9F; 0x11AA0; 0x11AA1; 0x11AA2; 0x11B00; 0x11B01; - 0x11B02; 0x11B03; 0x11B04; 0x11B05; 0x11B06; 0x11B07; 0x11B08; 0x11B09; - 0x11BE1; 0x11C41; 0x11C42; 0x11C43; 0x11C44; 0x11C45; 0x11C70; 0x11C71; - 0x11EF7; 0x11EF8; 0x11F43; 0x11F44; 0x11F45; 0x11F46; 0x11F47; 0x11F48; - 0x11F49; 0x11F4A; 0x11F4B; 0x11F4C; 0x11F4D; 0x11F4E; 0x11F4F; 0x11FFF; - 0x12470; 0x12471; 0x12472; 0x12473; 0x12474; 0x12FF1; 0x12FF2; 0x16A6E; - 0x16A6F; 0x16AF5; 0x16B37; 0x16B38; 0x16B39; 0x16B3A; 0x16B3B; 0x16B44; - 0x16D6D; 0x16D6E; 0x16D6F; 0x16E97; 0x16E98; 0x16E99; 0x16E9A; 0x16FE2; - 0x1BC9F; 0x1DA87; 0x1DA88; 0x1DA89; 0x1DA8A; 0x1DA8B; 0x1E5FF; 0x1E95E; - 0x1E95F|] - -let [@ocamlformat "disable"] case_fold = - [|0x0041, "\u{0061}"; 0x0042, "\u{0062}"; 0x0043, "\u{0063}"; - 0x0044, "\u{0064}"; 0x0045, "\u{0065}"; 0x0046, "\u{0066}"; - 0x0047, "\u{0067}"; 0x0048, "\u{0068}"; 0x0049, "\u{0069}"; - 0x004A, "\u{006A}"; 0x004B, "\u{006B}"; 0x004C, "\u{006C}"; - 0x004D, "\u{006D}"; 0x004E, "\u{006E}"; 0x004F, "\u{006F}"; - 0x0050, "\u{0070}"; 0x0051, "\u{0071}"; 0x0052, "\u{0072}"; - 0x0053, "\u{0073}"; 0x0054, "\u{0074}"; 0x0055, "\u{0075}"; - 0x0056, "\u{0076}"; 0x0057, "\u{0077}"; 0x0058, "\u{0078}"; - 0x0059, "\u{0079}"; 0x005A, "\u{007A}"; 0x00B5, "\u{03BC}"; - 0x00C0, "\u{00E0}"; 0x00C1, "\u{00E1}"; 0x00C2, "\u{00E2}"; - 0x00C3, "\u{00E3}"; 0x00C4, "\u{00E4}"; 0x00C5, "\u{00E5}"; - 0x00C6, "\u{00E6}"; 0x00C7, "\u{00E7}"; 0x00C8, "\u{00E8}"; - 0x00C9, "\u{00E9}"; 0x00CA, "\u{00EA}"; 0x00CB, "\u{00EB}"; - 0x00CC, "\u{00EC}"; 0x00CD, "\u{00ED}"; 0x00CE, "\u{00EE}"; - 0x00CF, "\u{00EF}"; 0x00D0, "\u{00F0}"; 0x00D1, "\u{00F1}"; - 0x00D2, "\u{00F2}"; 0x00D3, "\u{00F3}"; 0x00D4, "\u{00F4}"; - 0x00D5, "\u{00F5}"; 0x00D6, "\u{00F6}"; 0x00D8, "\u{00F8}"; - 0x00D9, "\u{00F9}"; 0x00DA, "\u{00FA}"; 0x00DB, "\u{00FB}"; - 0x00DC, "\u{00FC}"; 0x00DD, "\u{00FD}"; 0x00DE, "\u{00FE}"; - 0x00DF, "\u{0073}\u{0073}"; 0x0100, "\u{0101}"; 0x0102, "\u{0103}"; - 0x0104, "\u{0105}"; 0x0106, "\u{0107}"; 0x0108, "\u{0109}"; - 0x010A, "\u{010B}"; 0x010C, "\u{010D}"; 0x010E, "\u{010F}"; - 0x0110, "\u{0111}"; 0x0112, "\u{0113}"; 0x0114, "\u{0115}"; - 0x0116, "\u{0117}"; 0x0118, "\u{0119}"; 0x011A, "\u{011B}"; - 0x011C, "\u{011D}"; 0x011E, "\u{011F}"; 0x0120, "\u{0121}"; - 0x0122, "\u{0123}"; 0x0124, "\u{0125}"; 0x0126, "\u{0127}"; - 0x0128, "\u{0129}"; 0x012A, "\u{012B}"; 0x012C, "\u{012D}"; - 0x012E, "\u{012F}"; 0x0130, "\u{0069}\u{0307}"; 0x0132, "\u{0133}"; - 0x0134, "\u{0135}"; 0x0136, "\u{0137}"; 0x0139, "\u{013A}"; - 0x013B, "\u{013C}"; 0x013D, "\u{013E}"; 0x013F, "\u{0140}"; - 0x0141, "\u{0142}"; 0x0143, "\u{0144}"; 0x0145, "\u{0146}"; - 0x0147, "\u{0148}"; 0x0149, "\u{02BC}\u{006E}"; 0x014A, "\u{014B}"; - 0x014C, "\u{014D}"; 0x014E, "\u{014F}"; 0x0150, "\u{0151}"; - 0x0152, "\u{0153}"; 0x0154, "\u{0155}"; 0x0156, "\u{0157}"; - 0x0158, "\u{0159}"; 0x015A, "\u{015B}"; 0x015C, "\u{015D}"; - 0x015E, "\u{015F}"; 0x0160, "\u{0161}"; 0x0162, "\u{0163}"; - 0x0164, "\u{0165}"; 0x0166, "\u{0167}"; 0x0168, "\u{0169}"; - 0x016A, "\u{016B}"; 0x016C, "\u{016D}"; 0x016E, "\u{016F}"; - 0x0170, "\u{0171}"; 0x0172, "\u{0173}"; 0x0174, "\u{0175}"; - 0x0176, "\u{0177}"; 0x0178, "\u{00FF}"; 0x0179, "\u{017A}"; - 0x017B, "\u{017C}"; 0x017D, "\u{017E}"; 0x017F, "\u{0073}"; - 0x0181, "\u{0253}"; 0x0182, "\u{0183}"; 0x0184, "\u{0185}"; - 0x0186, "\u{0254}"; 0x0187, "\u{0188}"; 0x0189, "\u{0256}"; - 0x018A, "\u{0257}"; 0x018B, "\u{018C}"; 0x018E, "\u{01DD}"; - 0x018F, "\u{0259}"; 0x0190, "\u{025B}"; 0x0191, "\u{0192}"; - 0x0193, "\u{0260}"; 0x0194, "\u{0263}"; 0x0196, "\u{0269}"; - 0x0197, "\u{0268}"; 0x0198, "\u{0199}"; 0x019C, "\u{026F}"; - 0x019D, "\u{0272}"; 0x019F, "\u{0275}"; 0x01A0, "\u{01A1}"; - 0x01A2, "\u{01A3}"; 0x01A4, "\u{01A5}"; 0x01A6, "\u{0280}"; - 0x01A7, "\u{01A8}"; 0x01A9, "\u{0283}"; 0x01AC, "\u{01AD}"; - 0x01AE, "\u{0288}"; 0x01AF, "\u{01B0}"; 0x01B1, "\u{028A}"; - 0x01B2, "\u{028B}"; 0x01B3, "\u{01B4}"; 0x01B5, "\u{01B6}"; - 0x01B7, "\u{0292}"; 0x01B8, "\u{01B9}"; 0x01BC, "\u{01BD}"; - 0x01C4, "\u{01C6}"; 0x01C5, "\u{01C6}"; 0x01C7, "\u{01C9}"; - 0x01C8, "\u{01C9}"; 0x01CA, "\u{01CC}"; 0x01CB, "\u{01CC}"; - 0x01CD, "\u{01CE}"; 0x01CF, "\u{01D0}"; 0x01D1, "\u{01D2}"; - 0x01D3, "\u{01D4}"; 0x01D5, "\u{01D6}"; 0x01D7, "\u{01D8}"; - 0x01D9, "\u{01DA}"; 0x01DB, "\u{01DC}"; 0x01DE, "\u{01DF}"; - 0x01E0, "\u{01E1}"; 0x01E2, "\u{01E3}"; 0x01E4, "\u{01E5}"; - 0x01E6, "\u{01E7}"; 0x01E8, "\u{01E9}"; 0x01EA, "\u{01EB}"; - 0x01EC, "\u{01ED}"; 0x01EE, "\u{01EF}"; 0x01F0, "\u{006A}\u{030C}"; - 0x01F1, "\u{01F3}"; 0x01F2, "\u{01F3}"; 0x01F4, "\u{01F5}"; - 0x01F6, "\u{0195}"; 0x01F7, "\u{01BF}"; 0x01F8, "\u{01F9}"; - 0x01FA, "\u{01FB}"; 0x01FC, "\u{01FD}"; 0x01FE, "\u{01FF}"; - 0x0200, "\u{0201}"; 0x0202, "\u{0203}"; 0x0204, "\u{0205}"; - 0x0206, "\u{0207}"; 0x0208, "\u{0209}"; 0x020A, "\u{020B}"; - 0x020C, "\u{020D}"; 0x020E, "\u{020F}"; 0x0210, "\u{0211}"; - 0x0212, "\u{0213}"; 0x0214, "\u{0215}"; 0x0216, "\u{0217}"; - 0x0218, "\u{0219}"; 0x021A, "\u{021B}"; 0x021C, "\u{021D}"; - 0x021E, "\u{021F}"; 0x0220, "\u{019E}"; 0x0222, "\u{0223}"; - 0x0224, "\u{0225}"; 0x0226, "\u{0227}"; 0x0228, "\u{0229}"; - 0x022A, "\u{022B}"; 0x022C, "\u{022D}"; 0x022E, "\u{022F}"; - 0x0230, "\u{0231}"; 0x0232, "\u{0233}"; 0x023A, "\u{2C65}"; - 0x023B, "\u{023C}"; 0x023D, "\u{019A}"; 0x023E, "\u{2C66}"; - 0x0241, "\u{0242}"; 0x0243, "\u{0180}"; 0x0244, "\u{0289}"; - 0x0245, "\u{028C}"; 0x0246, "\u{0247}"; 0x0248, "\u{0249}"; - 0x024A, "\u{024B}"; 0x024C, "\u{024D}"; 0x024E, "\u{024F}"; - 0x0345, "\u{03B9}"; 0x0370, "\u{0371}"; 0x0372, "\u{0373}"; - 0x0376, "\u{0377}"; 0x037F, "\u{03F3}"; 0x0386, "\u{03AC}"; - 0x0388, "\u{03AD}"; 0x0389, "\u{03AE}"; 0x038A, "\u{03AF}"; - 0x038C, "\u{03CC}"; 0x038E, "\u{03CD}"; 0x038F, "\u{03CE}"; - 0x0390, "\u{03B9}\u{0308}\u{0301}"; 0x0391, "\u{03B1}"; - 0x0392, "\u{03B2}"; 0x0393, "\u{03B3}"; 0x0394, "\u{03B4}"; - 0x0395, "\u{03B5}"; 0x0396, "\u{03B6}"; 0x0397, "\u{03B7}"; - 0x0398, "\u{03B8}"; 0x0399, "\u{03B9}"; 0x039A, "\u{03BA}"; - 0x039B, "\u{03BB}"; 0x039C, "\u{03BC}"; 0x039D, "\u{03BD}"; - 0x039E, "\u{03BE}"; 0x039F, "\u{03BF}"; 0x03A0, "\u{03C0}"; - 0x03A1, "\u{03C1}"; 0x03A3, "\u{03C3}"; 0x03A4, "\u{03C4}"; - 0x03A5, "\u{03C5}"; 0x03A6, "\u{03C6}"; 0x03A7, "\u{03C7}"; - 0x03A8, "\u{03C8}"; 0x03A9, "\u{03C9}"; 0x03AA, "\u{03CA}"; - 0x03AB, "\u{03CB}"; 0x03B0, "\u{03C5}\u{0308}\u{0301}"; - 0x03C2, "\u{03C3}"; 0x03CF, "\u{03D7}"; 0x03D0, "\u{03B2}"; - 0x03D1, "\u{03B8}"; 0x03D5, "\u{03C6}"; 0x03D6, "\u{03C0}"; - 0x03D8, "\u{03D9}"; 0x03DA, "\u{03DB}"; 0x03DC, "\u{03DD}"; - 0x03DE, "\u{03DF}"; 0x03E0, "\u{03E1}"; 0x03E2, "\u{03E3}"; - 0x03E4, "\u{03E5}"; 0x03E6, "\u{03E7}"; 0x03E8, "\u{03E9}"; - 0x03EA, "\u{03EB}"; 0x03EC, "\u{03ED}"; 0x03EE, "\u{03EF}"; - 0x03F0, "\u{03BA}"; 0x03F1, "\u{03C1}"; 0x03F4, "\u{03B8}"; - 0x03F5, "\u{03B5}"; 0x03F7, "\u{03F8}"; 0x03F9, "\u{03F2}"; - 0x03FA, "\u{03FB}"; 0x03FD, "\u{037B}"; 0x03FE, "\u{037C}"; - 0x03FF, "\u{037D}"; 0x0400, "\u{0450}"; 0x0401, "\u{0451}"; - 0x0402, "\u{0452}"; 0x0403, "\u{0453}"; 0x0404, "\u{0454}"; - 0x0405, "\u{0455}"; 0x0406, "\u{0456}"; 0x0407, "\u{0457}"; - 0x0408, "\u{0458}"; 0x0409, "\u{0459}"; 0x040A, "\u{045A}"; - 0x040B, "\u{045B}"; 0x040C, "\u{045C}"; 0x040D, "\u{045D}"; - 0x040E, "\u{045E}"; 0x040F, "\u{045F}"; 0x0410, "\u{0430}"; - 0x0411, "\u{0431}"; 0x0412, "\u{0432}"; 0x0413, "\u{0433}"; - 0x0414, "\u{0434}"; 0x0415, "\u{0435}"; 0x0416, "\u{0436}"; - 0x0417, "\u{0437}"; 0x0418, "\u{0438}"; 0x0419, "\u{0439}"; - 0x041A, "\u{043A}"; 0x041B, "\u{043B}"; 0x041C, "\u{043C}"; - 0x041D, "\u{043D}"; 0x041E, "\u{043E}"; 0x041F, "\u{043F}"; - 0x0420, "\u{0440}"; 0x0421, "\u{0441}"; 0x0422, "\u{0442}"; - 0x0423, "\u{0443}"; 0x0424, "\u{0444}"; 0x0425, "\u{0445}"; - 0x0426, "\u{0446}"; 0x0427, "\u{0447}"; 0x0428, "\u{0448}"; - 0x0429, "\u{0449}"; 0x042A, "\u{044A}"; 0x042B, "\u{044B}"; - 0x042C, "\u{044C}"; 0x042D, "\u{044D}"; 0x042E, "\u{044E}"; - 0x042F, "\u{044F}"; 0x0460, "\u{0461}"; 0x0462, "\u{0463}"; - 0x0464, "\u{0465}"; 0x0466, "\u{0467}"; 0x0468, "\u{0469}"; - 0x046A, "\u{046B}"; 0x046C, "\u{046D}"; 0x046E, "\u{046F}"; - 0x0470, "\u{0471}"; 0x0472, "\u{0473}"; 0x0474, "\u{0475}"; - 0x0476, "\u{0477}"; 0x0478, "\u{0479}"; 0x047A, "\u{047B}"; - 0x047C, "\u{047D}"; 0x047E, "\u{047F}"; 0x0480, "\u{0481}"; - 0x048A, "\u{048B}"; 0x048C, "\u{048D}"; 0x048E, "\u{048F}"; - 0x0490, "\u{0491}"; 0x0492, "\u{0493}"; 0x0494, "\u{0495}"; - 0x0496, "\u{0497}"; 0x0498, "\u{0499}"; 0x049A, "\u{049B}"; - 0x049C, "\u{049D}"; 0x049E, "\u{049F}"; 0x04A0, "\u{04A1}"; - 0x04A2, "\u{04A3}"; 0x04A4, "\u{04A5}"; 0x04A6, "\u{04A7}"; - 0x04A8, "\u{04A9}"; 0x04AA, "\u{04AB}"; 0x04AC, "\u{04AD}"; - 0x04AE, "\u{04AF}"; 0x04B0, "\u{04B1}"; 0x04B2, "\u{04B3}"; - 0x04B4, "\u{04B5}"; 0x04B6, "\u{04B7}"; 0x04B8, "\u{04B9}"; - 0x04BA, "\u{04BB}"; 0x04BC, "\u{04BD}"; 0x04BE, "\u{04BF}"; - 0x04C0, "\u{04CF}"; 0x04C1, "\u{04C2}"; 0x04C3, "\u{04C4}"; - 0x04C5, "\u{04C6}"; 0x04C7, "\u{04C8}"; 0x04C9, "\u{04CA}"; - 0x04CB, "\u{04CC}"; 0x04CD, "\u{04CE}"; 0x04D0, "\u{04D1}"; - 0x04D2, "\u{04D3}"; 0x04D4, "\u{04D5}"; 0x04D6, "\u{04D7}"; - 0x04D8, "\u{04D9}"; 0x04DA, "\u{04DB}"; 0x04DC, "\u{04DD}"; - 0x04DE, "\u{04DF}"; 0x04E0, "\u{04E1}"; 0x04E2, "\u{04E3}"; - 0x04E4, "\u{04E5}"; 0x04E6, "\u{04E7}"; 0x04E8, "\u{04E9}"; - 0x04EA, "\u{04EB}"; 0x04EC, "\u{04ED}"; 0x04EE, "\u{04EF}"; - 0x04F0, "\u{04F1}"; 0x04F2, "\u{04F3}"; 0x04F4, "\u{04F5}"; - 0x04F6, "\u{04F7}"; 0x04F8, "\u{04F9}"; 0x04FA, "\u{04FB}"; - 0x04FC, "\u{04FD}"; 0x04FE, "\u{04FF}"; 0x0500, "\u{0501}"; - 0x0502, "\u{0503}"; 0x0504, "\u{0505}"; 0x0506, "\u{0507}"; - 0x0508, "\u{0509}"; 0x050A, "\u{050B}"; 0x050C, "\u{050D}"; - 0x050E, "\u{050F}"; 0x0510, "\u{0511}"; 0x0512, "\u{0513}"; - 0x0514, "\u{0515}"; 0x0516, "\u{0517}"; 0x0518, "\u{0519}"; - 0x051A, "\u{051B}"; 0x051C, "\u{051D}"; 0x051E, "\u{051F}"; - 0x0520, "\u{0521}"; 0x0522, "\u{0523}"; 0x0524, "\u{0525}"; - 0x0526, "\u{0527}"; 0x0528, "\u{0529}"; 0x052A, "\u{052B}"; - 0x052C, "\u{052D}"; 0x052E, "\u{052F}"; 0x0531, "\u{0561}"; - 0x0532, "\u{0562}"; 0x0533, "\u{0563}"; 0x0534, "\u{0564}"; - 0x0535, "\u{0565}"; 0x0536, "\u{0566}"; 0x0537, "\u{0567}"; - 0x0538, "\u{0568}"; 0x0539, "\u{0569}"; 0x053A, "\u{056A}"; - 0x053B, "\u{056B}"; 0x053C, "\u{056C}"; 0x053D, "\u{056D}"; - 0x053E, "\u{056E}"; 0x053F, "\u{056F}"; 0x0540, "\u{0570}"; - 0x0541, "\u{0571}"; 0x0542, "\u{0572}"; 0x0543, "\u{0573}"; - 0x0544, "\u{0574}"; 0x0545, "\u{0575}"; 0x0546, "\u{0576}"; - 0x0547, "\u{0577}"; 0x0548, "\u{0578}"; 0x0549, "\u{0579}"; - 0x054A, "\u{057A}"; 0x054B, "\u{057B}"; 0x054C, "\u{057C}"; - 0x054D, "\u{057D}"; 0x054E, "\u{057E}"; 0x054F, "\u{057F}"; - 0x0550, "\u{0580}"; 0x0551, "\u{0581}"; 0x0552, "\u{0582}"; - 0x0553, "\u{0583}"; 0x0554, "\u{0584}"; 0x0555, "\u{0585}"; - 0x0556, "\u{0586}"; 0x0587, "\u{0565}\u{0582}"; 0x10A0, "\u{2D00}"; - 0x10A1, "\u{2D01}"; 0x10A2, "\u{2D02}"; 0x10A3, "\u{2D03}"; - 0x10A4, "\u{2D04}"; 0x10A5, "\u{2D05}"; 0x10A6, "\u{2D06}"; - 0x10A7, "\u{2D07}"; 0x10A8, "\u{2D08}"; 0x10A9, "\u{2D09}"; - 0x10AA, "\u{2D0A}"; 0x10AB, "\u{2D0B}"; 0x10AC, "\u{2D0C}"; - 0x10AD, "\u{2D0D}"; 0x10AE, "\u{2D0E}"; 0x10AF, "\u{2D0F}"; - 0x10B0, "\u{2D10}"; 0x10B1, "\u{2D11}"; 0x10B2, "\u{2D12}"; - 0x10B3, "\u{2D13}"; 0x10B4, "\u{2D14}"; 0x10B5, "\u{2D15}"; - 0x10B6, "\u{2D16}"; 0x10B7, "\u{2D17}"; 0x10B8, "\u{2D18}"; - 0x10B9, "\u{2D19}"; 0x10BA, "\u{2D1A}"; 0x10BB, "\u{2D1B}"; - 0x10BC, "\u{2D1C}"; 0x10BD, "\u{2D1D}"; 0x10BE, "\u{2D1E}"; - 0x10BF, "\u{2D1F}"; 0x10C0, "\u{2D20}"; 0x10C1, "\u{2D21}"; - 0x10C2, "\u{2D22}"; 0x10C3, "\u{2D23}"; 0x10C4, "\u{2D24}"; - 0x10C5, "\u{2D25}"; 0x10C7, "\u{2D27}"; 0x10CD, "\u{2D2D}"; - 0x13F8, "\u{13F0}"; 0x13F9, "\u{13F1}"; 0x13FA, "\u{13F2}"; - 0x13FB, "\u{13F3}"; 0x13FC, "\u{13F4}"; 0x13FD, "\u{13F5}"; - 0x1C80, "\u{0432}"; 0x1C81, "\u{0434}"; 0x1C82, "\u{043E}"; - 0x1C83, "\u{0441}"; 0x1C84, "\u{0442}"; 0x1C85, "\u{0442}"; - 0x1C86, "\u{044A}"; 0x1C87, "\u{0463}"; 0x1C88, "\u{A64B}"; - 0x1C89, "\u{1C8A}"; 0x1C90, "\u{10D0}"; 0x1C91, "\u{10D1}"; - 0x1C92, "\u{10D2}"; 0x1C93, "\u{10D3}"; 0x1C94, "\u{10D4}"; - 0x1C95, "\u{10D5}"; 0x1C96, "\u{10D6}"; 0x1C97, "\u{10D7}"; - 0x1C98, "\u{10D8}"; 0x1C99, "\u{10D9}"; 0x1C9A, "\u{10DA}"; - 0x1C9B, "\u{10DB}"; 0x1C9C, "\u{10DC}"; 0x1C9D, "\u{10DD}"; - 0x1C9E, "\u{10DE}"; 0x1C9F, "\u{10DF}"; 0x1CA0, "\u{10E0}"; - 0x1CA1, "\u{10E1}"; 0x1CA2, "\u{10E2}"; 0x1CA3, "\u{10E3}"; - 0x1CA4, "\u{10E4}"; 0x1CA5, "\u{10E5}"; 0x1CA6, "\u{10E6}"; - 0x1CA7, "\u{10E7}"; 0x1CA8, "\u{10E8}"; 0x1CA9, "\u{10E9}"; - 0x1CAA, "\u{10EA}"; 0x1CAB, "\u{10EB}"; 0x1CAC, "\u{10EC}"; - 0x1CAD, "\u{10ED}"; 0x1CAE, "\u{10EE}"; 0x1CAF, "\u{10EF}"; - 0x1CB0, "\u{10F0}"; 0x1CB1, "\u{10F1}"; 0x1CB2, "\u{10F2}"; - 0x1CB3, "\u{10F3}"; 0x1CB4, "\u{10F4}"; 0x1CB5, "\u{10F5}"; - 0x1CB6, "\u{10F6}"; 0x1CB7, "\u{10F7}"; 0x1CB8, "\u{10F8}"; - 0x1CB9, "\u{10F9}"; 0x1CBA, "\u{10FA}"; 0x1CBD, "\u{10FD}"; - 0x1CBE, "\u{10FE}"; 0x1CBF, "\u{10FF}"; 0x1E00, "\u{1E01}"; - 0x1E02, "\u{1E03}"; 0x1E04, "\u{1E05}"; 0x1E06, "\u{1E07}"; - 0x1E08, "\u{1E09}"; 0x1E0A, "\u{1E0B}"; 0x1E0C, "\u{1E0D}"; - 0x1E0E, "\u{1E0F}"; 0x1E10, "\u{1E11}"; 0x1E12, "\u{1E13}"; - 0x1E14, "\u{1E15}"; 0x1E16, "\u{1E17}"; 0x1E18, "\u{1E19}"; - 0x1E1A, "\u{1E1B}"; 0x1E1C, "\u{1E1D}"; 0x1E1E, "\u{1E1F}"; - 0x1E20, "\u{1E21}"; 0x1E22, "\u{1E23}"; 0x1E24, "\u{1E25}"; - 0x1E26, "\u{1E27}"; 0x1E28, "\u{1E29}"; 0x1E2A, "\u{1E2B}"; - 0x1E2C, "\u{1E2D}"; 0x1E2E, "\u{1E2F}"; 0x1E30, "\u{1E31}"; - 0x1E32, "\u{1E33}"; 0x1E34, "\u{1E35}"; 0x1E36, "\u{1E37}"; - 0x1E38, "\u{1E39}"; 0x1E3A, "\u{1E3B}"; 0x1E3C, "\u{1E3D}"; - 0x1E3E, "\u{1E3F}"; 0x1E40, "\u{1E41}"; 0x1E42, "\u{1E43}"; - 0x1E44, "\u{1E45}"; 0x1E46, "\u{1E47}"; 0x1E48, "\u{1E49}"; - 0x1E4A, "\u{1E4B}"; 0x1E4C, "\u{1E4D}"; 0x1E4E, "\u{1E4F}"; - 0x1E50, "\u{1E51}"; 0x1E52, "\u{1E53}"; 0x1E54, "\u{1E55}"; - 0x1E56, "\u{1E57}"; 0x1E58, "\u{1E59}"; 0x1E5A, "\u{1E5B}"; - 0x1E5C, "\u{1E5D}"; 0x1E5E, "\u{1E5F}"; 0x1E60, "\u{1E61}"; - 0x1E62, "\u{1E63}"; 0x1E64, "\u{1E65}"; 0x1E66, "\u{1E67}"; - 0x1E68, "\u{1E69}"; 0x1E6A, "\u{1E6B}"; 0x1E6C, "\u{1E6D}"; - 0x1E6E, "\u{1E6F}"; 0x1E70, "\u{1E71}"; 0x1E72, "\u{1E73}"; - 0x1E74, "\u{1E75}"; 0x1E76, "\u{1E77}"; 0x1E78, "\u{1E79}"; - 0x1E7A, "\u{1E7B}"; 0x1E7C, "\u{1E7D}"; 0x1E7E, "\u{1E7F}"; - 0x1E80, "\u{1E81}"; 0x1E82, "\u{1E83}"; 0x1E84, "\u{1E85}"; - 0x1E86, "\u{1E87}"; 0x1E88, "\u{1E89}"; 0x1E8A, "\u{1E8B}"; - 0x1E8C, "\u{1E8D}"; 0x1E8E, "\u{1E8F}"; 0x1E90, "\u{1E91}"; - 0x1E92, "\u{1E93}"; 0x1E94, "\u{1E95}"; 0x1E96, "\u{0068}\u{0331}"; - 0x1E97, "\u{0074}\u{0308}"; 0x1E98, "\u{0077}\u{030A}"; - 0x1E99, "\u{0079}\u{030A}"; 0x1E9A, "\u{0061}\u{02BE}"; - 0x1E9B, "\u{1E61}"; 0x1E9E, "\u{0073}\u{0073}"; 0x1EA0, "\u{1EA1}"; - 0x1EA2, "\u{1EA3}"; 0x1EA4, "\u{1EA5}"; 0x1EA6, "\u{1EA7}"; - 0x1EA8, "\u{1EA9}"; 0x1EAA, "\u{1EAB}"; 0x1EAC, "\u{1EAD}"; - 0x1EAE, "\u{1EAF}"; 0x1EB0, "\u{1EB1}"; 0x1EB2, "\u{1EB3}"; - 0x1EB4, "\u{1EB5}"; 0x1EB6, "\u{1EB7}"; 0x1EB8, "\u{1EB9}"; - 0x1EBA, "\u{1EBB}"; 0x1EBC, "\u{1EBD}"; 0x1EBE, "\u{1EBF}"; - 0x1EC0, "\u{1EC1}"; 0x1EC2, "\u{1EC3}"; 0x1EC4, "\u{1EC5}"; - 0x1EC6, "\u{1EC7}"; 0x1EC8, "\u{1EC9}"; 0x1ECA, "\u{1ECB}"; - 0x1ECC, "\u{1ECD}"; 0x1ECE, "\u{1ECF}"; 0x1ED0, "\u{1ED1}"; - 0x1ED2, "\u{1ED3}"; 0x1ED4, "\u{1ED5}"; 0x1ED6, "\u{1ED7}"; - 0x1ED8, "\u{1ED9}"; 0x1EDA, "\u{1EDB}"; 0x1EDC, "\u{1EDD}"; - 0x1EDE, "\u{1EDF}"; 0x1EE0, "\u{1EE1}"; 0x1EE2, "\u{1EE3}"; - 0x1EE4, "\u{1EE5}"; 0x1EE6, "\u{1EE7}"; 0x1EE8, "\u{1EE9}"; - 0x1EEA, "\u{1EEB}"; 0x1EEC, "\u{1EED}"; 0x1EEE, "\u{1EEF}"; - 0x1EF0, "\u{1EF1}"; 0x1EF2, "\u{1EF3}"; 0x1EF4, "\u{1EF5}"; - 0x1EF6, "\u{1EF7}"; 0x1EF8, "\u{1EF9}"; 0x1EFA, "\u{1EFB}"; - 0x1EFC, "\u{1EFD}"; 0x1EFE, "\u{1EFF}"; 0x1F08, "\u{1F00}"; - 0x1F09, "\u{1F01}"; 0x1F0A, "\u{1F02}"; 0x1F0B, "\u{1F03}"; - 0x1F0C, "\u{1F04}"; 0x1F0D, "\u{1F05}"; 0x1F0E, "\u{1F06}"; - 0x1F0F, "\u{1F07}"; 0x1F18, "\u{1F10}"; 0x1F19, "\u{1F11}"; - 0x1F1A, "\u{1F12}"; 0x1F1B, "\u{1F13}"; 0x1F1C, "\u{1F14}"; - 0x1F1D, "\u{1F15}"; 0x1F28, "\u{1F20}"; 0x1F29, "\u{1F21}"; - 0x1F2A, "\u{1F22}"; 0x1F2B, "\u{1F23}"; 0x1F2C, "\u{1F24}"; - 0x1F2D, "\u{1F25}"; 0x1F2E, "\u{1F26}"; 0x1F2F, "\u{1F27}"; - 0x1F38, "\u{1F30}"; 0x1F39, "\u{1F31}"; 0x1F3A, "\u{1F32}"; - 0x1F3B, "\u{1F33}"; 0x1F3C, "\u{1F34}"; 0x1F3D, "\u{1F35}"; - 0x1F3E, "\u{1F36}"; 0x1F3F, "\u{1F37}"; 0x1F48, "\u{1F40}"; - 0x1F49, "\u{1F41}"; 0x1F4A, "\u{1F42}"; 0x1F4B, "\u{1F43}"; - 0x1F4C, "\u{1F44}"; 0x1F4D, "\u{1F45}"; 0x1F50, "\u{03C5}\u{0313}"; - 0x1F52, "\u{03C5}\u{0313}\u{0300}"; 0x1F54, "\u{03C5}\u{0313}\u{0301}"; - 0x1F56, "\u{03C5}\u{0313}\u{0342}"; 0x1F59, "\u{1F51}"; - 0x1F5B, "\u{1F53}"; 0x1F5D, "\u{1F55}"; 0x1F5F, "\u{1F57}"; - 0x1F68, "\u{1F60}"; 0x1F69, "\u{1F61}"; 0x1F6A, "\u{1F62}"; - 0x1F6B, "\u{1F63}"; 0x1F6C, "\u{1F64}"; 0x1F6D, "\u{1F65}"; - 0x1F6E, "\u{1F66}"; 0x1F6F, "\u{1F67}"; 0x1F80, "\u{1F00}\u{03B9}"; - 0x1F81, "\u{1F01}\u{03B9}"; 0x1F82, "\u{1F02}\u{03B9}"; - 0x1F83, "\u{1F03}\u{03B9}"; 0x1F84, "\u{1F04}\u{03B9}"; - 0x1F85, "\u{1F05}\u{03B9}"; 0x1F86, "\u{1F06}\u{03B9}"; - 0x1F87, "\u{1F07}\u{03B9}"; 0x1F88, "\u{1F00}\u{03B9}"; - 0x1F89, "\u{1F01}\u{03B9}"; 0x1F8A, "\u{1F02}\u{03B9}"; - 0x1F8B, "\u{1F03}\u{03B9}"; 0x1F8C, "\u{1F04}\u{03B9}"; - 0x1F8D, "\u{1F05}\u{03B9}"; 0x1F8E, "\u{1F06}\u{03B9}"; - 0x1F8F, "\u{1F07}\u{03B9}"; 0x1F90, "\u{1F20}\u{03B9}"; - 0x1F91, "\u{1F21}\u{03B9}"; 0x1F92, "\u{1F22}\u{03B9}"; - 0x1F93, "\u{1F23}\u{03B9}"; 0x1F94, "\u{1F24}\u{03B9}"; - 0x1F95, "\u{1F25}\u{03B9}"; 0x1F96, "\u{1F26}\u{03B9}"; - 0x1F97, "\u{1F27}\u{03B9}"; 0x1F98, "\u{1F20}\u{03B9}"; - 0x1F99, "\u{1F21}\u{03B9}"; 0x1F9A, "\u{1F22}\u{03B9}"; - 0x1F9B, "\u{1F23}\u{03B9}"; 0x1F9C, "\u{1F24}\u{03B9}"; - 0x1F9D, "\u{1F25}\u{03B9}"; 0x1F9E, "\u{1F26}\u{03B9}"; - 0x1F9F, "\u{1F27}\u{03B9}"; 0x1FA0, "\u{1F60}\u{03B9}"; - 0x1FA1, "\u{1F61}\u{03B9}"; 0x1FA2, "\u{1F62}\u{03B9}"; - 0x1FA3, "\u{1F63}\u{03B9}"; 0x1FA4, "\u{1F64}\u{03B9}"; - 0x1FA5, "\u{1F65}\u{03B9}"; 0x1FA6, "\u{1F66}\u{03B9}"; - 0x1FA7, "\u{1F67}\u{03B9}"; 0x1FA8, "\u{1F60}\u{03B9}"; - 0x1FA9, "\u{1F61}\u{03B9}"; 0x1FAA, "\u{1F62}\u{03B9}"; - 0x1FAB, "\u{1F63}\u{03B9}"; 0x1FAC, "\u{1F64}\u{03B9}"; - 0x1FAD, "\u{1F65}\u{03B9}"; 0x1FAE, "\u{1F66}\u{03B9}"; - 0x1FAF, "\u{1F67}\u{03B9}"; 0x1FB2, "\u{1F70}\u{03B9}"; - 0x1FB3, "\u{03B1}\u{03B9}"; 0x1FB4, "\u{03AC}\u{03B9}"; - 0x1FB6, "\u{03B1}\u{0342}"; 0x1FB7, "\u{03B1}\u{0342}\u{03B9}"; - 0x1FB8, "\u{1FB0}"; 0x1FB9, "\u{1FB1}"; 0x1FBA, "\u{1F70}"; - 0x1FBB, "\u{1F71}"; 0x1FBC, "\u{03B1}\u{03B9}"; 0x1FBE, "\u{03B9}"; - 0x1FC2, "\u{1F74}\u{03B9}"; 0x1FC3, "\u{03B7}\u{03B9}"; - 0x1FC4, "\u{03AE}\u{03B9}"; 0x1FC6, "\u{03B7}\u{0342}"; - 0x1FC7, "\u{03B7}\u{0342}\u{03B9}"; 0x1FC8, "\u{1F72}"; - 0x1FC9, "\u{1F73}"; 0x1FCA, "\u{1F74}"; 0x1FCB, "\u{1F75}"; - 0x1FCC, "\u{03B7}\u{03B9}"; 0x1FD2, "\u{03B9}\u{0308}\u{0300}"; - 0x1FD3, "\u{03B9}\u{0308}\u{0301}"; 0x1FD6, "\u{03B9}\u{0342}"; - 0x1FD7, "\u{03B9}\u{0308}\u{0342}"; 0x1FD8, "\u{1FD0}"; - 0x1FD9, "\u{1FD1}"; 0x1FDA, "\u{1F76}"; 0x1FDB, "\u{1F77}"; - 0x1FE2, "\u{03C5}\u{0308}\u{0300}"; 0x1FE3, "\u{03C5}\u{0308}\u{0301}"; - 0x1FE4, "\u{03C1}\u{0313}"; 0x1FE6, "\u{03C5}\u{0342}"; - 0x1FE7, "\u{03C5}\u{0308}\u{0342}"; 0x1FE8, "\u{1FE0}"; - 0x1FE9, "\u{1FE1}"; 0x1FEA, "\u{1F7A}"; 0x1FEB, "\u{1F7B}"; - 0x1FEC, "\u{1FE5}"; 0x1FF2, "\u{1F7C}\u{03B9}"; - 0x1FF3, "\u{03C9}\u{03B9}"; 0x1FF4, "\u{03CE}\u{03B9}"; - 0x1FF6, "\u{03C9}\u{0342}"; 0x1FF7, "\u{03C9}\u{0342}\u{03B9}"; - 0x1FF8, "\u{1F78}"; 0x1FF9, "\u{1F79}"; 0x1FFA, "\u{1F7C}"; - 0x1FFB, "\u{1F7D}"; 0x1FFC, "\u{03C9}\u{03B9}"; 0x2126, "\u{03C9}"; - 0x212A, "\u{006B}"; 0x212B, "\u{00E5}"; 0x2132, "\u{214E}"; - 0x2160, "\u{2170}"; 0x2161, "\u{2171}"; 0x2162, "\u{2172}"; - 0x2163, "\u{2173}"; 0x2164, "\u{2174}"; 0x2165, "\u{2175}"; - 0x2166, "\u{2176}"; 0x2167, "\u{2177}"; 0x2168, "\u{2178}"; - 0x2169, "\u{2179}"; 0x216A, "\u{217A}"; 0x216B, "\u{217B}"; - 0x216C, "\u{217C}"; 0x216D, "\u{217D}"; 0x216E, "\u{217E}"; - 0x216F, "\u{217F}"; 0x2183, "\u{2184}"; 0x24B6, "\u{24D0}"; - 0x24B7, "\u{24D1}"; 0x24B8, "\u{24D2}"; 0x24B9, "\u{24D3}"; - 0x24BA, "\u{24D4}"; 0x24BB, "\u{24D5}"; 0x24BC, "\u{24D6}"; - 0x24BD, "\u{24D7}"; 0x24BE, "\u{24D8}"; 0x24BF, "\u{24D9}"; - 0x24C0, "\u{24DA}"; 0x24C1, "\u{24DB}"; 0x24C2, "\u{24DC}"; - 0x24C3, "\u{24DD}"; 0x24C4, "\u{24DE}"; 0x24C5, "\u{24DF}"; - 0x24C6, "\u{24E0}"; 0x24C7, "\u{24E1}"; 0x24C8, "\u{24E2}"; - 0x24C9, "\u{24E3}"; 0x24CA, "\u{24E4}"; 0x24CB, "\u{24E5}"; - 0x24CC, "\u{24E6}"; 0x24CD, "\u{24E7}"; 0x24CE, "\u{24E8}"; - 0x24CF, "\u{24E9}"; 0x2C00, "\u{2C30}"; 0x2C01, "\u{2C31}"; - 0x2C02, "\u{2C32}"; 0x2C03, "\u{2C33}"; 0x2C04, "\u{2C34}"; - 0x2C05, "\u{2C35}"; 0x2C06, "\u{2C36}"; 0x2C07, "\u{2C37}"; - 0x2C08, "\u{2C38}"; 0x2C09, "\u{2C39}"; 0x2C0A, "\u{2C3A}"; - 0x2C0B, "\u{2C3B}"; 0x2C0C, "\u{2C3C}"; 0x2C0D, "\u{2C3D}"; - 0x2C0E, "\u{2C3E}"; 0x2C0F, "\u{2C3F}"; 0x2C10, "\u{2C40}"; - 0x2C11, "\u{2C41}"; 0x2C12, "\u{2C42}"; 0x2C13, "\u{2C43}"; - 0x2C14, "\u{2C44}"; 0x2C15, "\u{2C45}"; 0x2C16, "\u{2C46}"; - 0x2C17, "\u{2C47}"; 0x2C18, "\u{2C48}"; 0x2C19, "\u{2C49}"; - 0x2C1A, "\u{2C4A}"; 0x2C1B, "\u{2C4B}"; 0x2C1C, "\u{2C4C}"; - 0x2C1D, "\u{2C4D}"; 0x2C1E, "\u{2C4E}"; 0x2C1F, "\u{2C4F}"; - 0x2C20, "\u{2C50}"; 0x2C21, "\u{2C51}"; 0x2C22, "\u{2C52}"; - 0x2C23, "\u{2C53}"; 0x2C24, "\u{2C54}"; 0x2C25, "\u{2C55}"; - 0x2C26, "\u{2C56}"; 0x2C27, "\u{2C57}"; 0x2C28, "\u{2C58}"; - 0x2C29, "\u{2C59}"; 0x2C2A, "\u{2C5A}"; 0x2C2B, "\u{2C5B}"; - 0x2C2C, "\u{2C5C}"; 0x2C2D, "\u{2C5D}"; 0x2C2E, "\u{2C5E}"; - 0x2C2F, "\u{2C5F}"; 0x2C60, "\u{2C61}"; 0x2C62, "\u{026B}"; - 0x2C63, "\u{1D7D}"; 0x2C64, "\u{027D}"; 0x2C67, "\u{2C68}"; - 0x2C69, "\u{2C6A}"; 0x2C6B, "\u{2C6C}"; 0x2C6D, "\u{0251}"; - 0x2C6E, "\u{0271}"; 0x2C6F, "\u{0250}"; 0x2C70, "\u{0252}"; - 0x2C72, "\u{2C73}"; 0x2C75, "\u{2C76}"; 0x2C7E, "\u{023F}"; - 0x2C7F, "\u{0240}"; 0x2C80, "\u{2C81}"; 0x2C82, "\u{2C83}"; - 0x2C84, "\u{2C85}"; 0x2C86, "\u{2C87}"; 0x2C88, "\u{2C89}"; - 0x2C8A, "\u{2C8B}"; 0x2C8C, "\u{2C8D}"; 0x2C8E, "\u{2C8F}"; - 0x2C90, "\u{2C91}"; 0x2C92, "\u{2C93}"; 0x2C94, "\u{2C95}"; - 0x2C96, "\u{2C97}"; 0x2C98, "\u{2C99}"; 0x2C9A, "\u{2C9B}"; - 0x2C9C, "\u{2C9D}"; 0x2C9E, "\u{2C9F}"; 0x2CA0, "\u{2CA1}"; - 0x2CA2, "\u{2CA3}"; 0x2CA4, "\u{2CA5}"; 0x2CA6, "\u{2CA7}"; - 0x2CA8, "\u{2CA9}"; 0x2CAA, "\u{2CAB}"; 0x2CAC, "\u{2CAD}"; - 0x2CAE, "\u{2CAF}"; 0x2CB0, "\u{2CB1}"; 0x2CB2, "\u{2CB3}"; - 0x2CB4, "\u{2CB5}"; 0x2CB6, "\u{2CB7}"; 0x2CB8, "\u{2CB9}"; - 0x2CBA, "\u{2CBB}"; 0x2CBC, "\u{2CBD}"; 0x2CBE, "\u{2CBF}"; - 0x2CC0, "\u{2CC1}"; 0x2CC2, "\u{2CC3}"; 0x2CC4, "\u{2CC5}"; - 0x2CC6, "\u{2CC7}"; 0x2CC8, "\u{2CC9}"; 0x2CCA, "\u{2CCB}"; - 0x2CCC, "\u{2CCD}"; 0x2CCE, "\u{2CCF}"; 0x2CD0, "\u{2CD1}"; - 0x2CD2, "\u{2CD3}"; 0x2CD4, "\u{2CD5}"; 0x2CD6, "\u{2CD7}"; - 0x2CD8, "\u{2CD9}"; 0x2CDA, "\u{2CDB}"; 0x2CDC, "\u{2CDD}"; - 0x2CDE, "\u{2CDF}"; 0x2CE0, "\u{2CE1}"; 0x2CE2, "\u{2CE3}"; - 0x2CEB, "\u{2CEC}"; 0x2CED, "\u{2CEE}"; 0x2CF2, "\u{2CF3}"; - 0xA640, "\u{A641}"; 0xA642, "\u{A643}"; 0xA644, "\u{A645}"; - 0xA646, "\u{A647}"; 0xA648, "\u{A649}"; 0xA64A, "\u{A64B}"; - 0xA64C, "\u{A64D}"; 0xA64E, "\u{A64F}"; 0xA650, "\u{A651}"; - 0xA652, "\u{A653}"; 0xA654, "\u{A655}"; 0xA656, "\u{A657}"; - 0xA658, "\u{A659}"; 0xA65A, "\u{A65B}"; 0xA65C, "\u{A65D}"; - 0xA65E, "\u{A65F}"; 0xA660, "\u{A661}"; 0xA662, "\u{A663}"; - 0xA664, "\u{A665}"; 0xA666, "\u{A667}"; 0xA668, "\u{A669}"; - 0xA66A, "\u{A66B}"; 0xA66C, "\u{A66D}"; 0xA680, "\u{A681}"; - 0xA682, "\u{A683}"; 0xA684, "\u{A685}"; 0xA686, "\u{A687}"; - 0xA688, "\u{A689}"; 0xA68A, "\u{A68B}"; 0xA68C, "\u{A68D}"; - 0xA68E, "\u{A68F}"; 0xA690, "\u{A691}"; 0xA692, "\u{A693}"; - 0xA694, "\u{A695}"; 0xA696, "\u{A697}"; 0xA698, "\u{A699}"; - 0xA69A, "\u{A69B}"; 0xA722, "\u{A723}"; 0xA724, "\u{A725}"; - 0xA726, "\u{A727}"; 0xA728, "\u{A729}"; 0xA72A, "\u{A72B}"; - 0xA72C, "\u{A72D}"; 0xA72E, "\u{A72F}"; 0xA732, "\u{A733}"; - 0xA734, "\u{A735}"; 0xA736, "\u{A737}"; 0xA738, "\u{A739}"; - 0xA73A, "\u{A73B}"; 0xA73C, "\u{A73D}"; 0xA73E, "\u{A73F}"; - 0xA740, "\u{A741}"; 0xA742, "\u{A743}"; 0xA744, "\u{A745}"; - 0xA746, "\u{A747}"; 0xA748, "\u{A749}"; 0xA74A, "\u{A74B}"; - 0xA74C, "\u{A74D}"; 0xA74E, "\u{A74F}"; 0xA750, "\u{A751}"; - 0xA752, "\u{A753}"; 0xA754, "\u{A755}"; 0xA756, "\u{A757}"; - 0xA758, "\u{A759}"; 0xA75A, "\u{A75B}"; 0xA75C, "\u{A75D}"; - 0xA75E, "\u{A75F}"; 0xA760, "\u{A761}"; 0xA762, "\u{A763}"; - 0xA764, "\u{A765}"; 0xA766, "\u{A767}"; 0xA768, "\u{A769}"; - 0xA76A, "\u{A76B}"; 0xA76C, "\u{A76D}"; 0xA76E, "\u{A76F}"; - 0xA779, "\u{A77A}"; 0xA77B, "\u{A77C}"; 0xA77D, "\u{1D79}"; - 0xA77E, "\u{A77F}"; 0xA780, "\u{A781}"; 0xA782, "\u{A783}"; - 0xA784, "\u{A785}"; 0xA786, "\u{A787}"; 0xA78B, "\u{A78C}"; - 0xA78D, "\u{0265}"; 0xA790, "\u{A791}"; 0xA792, "\u{A793}"; - 0xA796, "\u{A797}"; 0xA798, "\u{A799}"; 0xA79A, "\u{A79B}"; - 0xA79C, "\u{A79D}"; 0xA79E, "\u{A79F}"; 0xA7A0, "\u{A7A1}"; - 0xA7A2, "\u{A7A3}"; 0xA7A4, "\u{A7A5}"; 0xA7A6, "\u{A7A7}"; - 0xA7A8, "\u{A7A9}"; 0xA7AA, "\u{0266}"; 0xA7AB, "\u{025C}"; - 0xA7AC, "\u{0261}"; 0xA7AD, "\u{026C}"; 0xA7AE, "\u{026A}"; - 0xA7B0, "\u{029E}"; 0xA7B1, "\u{0287}"; 0xA7B2, "\u{029D}"; - 0xA7B3, "\u{AB53}"; 0xA7B4, "\u{A7B5}"; 0xA7B6, "\u{A7B7}"; - 0xA7B8, "\u{A7B9}"; 0xA7BA, "\u{A7BB}"; 0xA7BC, "\u{A7BD}"; - 0xA7BE, "\u{A7BF}"; 0xA7C0, "\u{A7C1}"; 0xA7C2, "\u{A7C3}"; - 0xA7C4, "\u{A794}"; 0xA7C5, "\u{0282}"; 0xA7C6, "\u{1D8E}"; - 0xA7C7, "\u{A7C8}"; 0xA7C9, "\u{A7CA}"; 0xA7CB, "\u{0264}"; - 0xA7CC, "\u{A7CD}"; 0xA7D0, "\u{A7D1}"; 0xA7D6, "\u{A7D7}"; - 0xA7D8, "\u{A7D9}"; 0xA7DA, "\u{A7DB}"; 0xA7DC, "\u{019B}"; - 0xA7F5, "\u{A7F6}"; 0xAB70, "\u{13A0}"; 0xAB71, "\u{13A1}"; - 0xAB72, "\u{13A2}"; 0xAB73, "\u{13A3}"; 0xAB74, "\u{13A4}"; - 0xAB75, "\u{13A5}"; 0xAB76, "\u{13A6}"; 0xAB77, "\u{13A7}"; - 0xAB78, "\u{13A8}"; 0xAB79, "\u{13A9}"; 0xAB7A, "\u{13AA}"; - 0xAB7B, "\u{13AB}"; 0xAB7C, "\u{13AC}"; 0xAB7D, "\u{13AD}"; - 0xAB7E, "\u{13AE}"; 0xAB7F, "\u{13AF}"; 0xAB80, "\u{13B0}"; - 0xAB81, "\u{13B1}"; 0xAB82, "\u{13B2}"; 0xAB83, "\u{13B3}"; - 0xAB84, "\u{13B4}"; 0xAB85, "\u{13B5}"; 0xAB86, "\u{13B6}"; - 0xAB87, "\u{13B7}"; 0xAB88, "\u{13B8}"; 0xAB89, "\u{13B9}"; - 0xAB8A, "\u{13BA}"; 0xAB8B, "\u{13BB}"; 0xAB8C, "\u{13BC}"; - 0xAB8D, "\u{13BD}"; 0xAB8E, "\u{13BE}"; 0xAB8F, "\u{13BF}"; - 0xAB90, "\u{13C0}"; 0xAB91, "\u{13C1}"; 0xAB92, "\u{13C2}"; - 0xAB93, "\u{13C3}"; 0xAB94, "\u{13C4}"; 0xAB95, "\u{13C5}"; - 0xAB96, "\u{13C6}"; 0xAB97, "\u{13C7}"; 0xAB98, "\u{13C8}"; - 0xAB99, "\u{13C9}"; 0xAB9A, "\u{13CA}"; 0xAB9B, "\u{13CB}"; - 0xAB9C, "\u{13CC}"; 0xAB9D, "\u{13CD}"; 0xAB9E, "\u{13CE}"; - 0xAB9F, "\u{13CF}"; 0xABA0, "\u{13D0}"; 0xABA1, "\u{13D1}"; - 0xABA2, "\u{13D2}"; 0xABA3, "\u{13D3}"; 0xABA4, "\u{13D4}"; - 0xABA5, "\u{13D5}"; 0xABA6, "\u{13D6}"; 0xABA7, "\u{13D7}"; - 0xABA8, "\u{13D8}"; 0xABA9, "\u{13D9}"; 0xABAA, "\u{13DA}"; - 0xABAB, "\u{13DB}"; 0xABAC, "\u{13DC}"; 0xABAD, "\u{13DD}"; - 0xABAE, "\u{13DE}"; 0xABAF, "\u{13DF}"; 0xABB0, "\u{13E0}"; - 0xABB1, "\u{13E1}"; 0xABB2, "\u{13E2}"; 0xABB3, "\u{13E3}"; - 0xABB4, "\u{13E4}"; 0xABB5, "\u{13E5}"; 0xABB6, "\u{13E6}"; - 0xABB7, "\u{13E7}"; 0xABB8, "\u{13E8}"; 0xABB9, "\u{13E9}"; - 0xABBA, "\u{13EA}"; 0xABBB, "\u{13EB}"; 0xABBC, "\u{13EC}"; - 0xABBD, "\u{13ED}"; 0xABBE, "\u{13EE}"; 0xABBF, "\u{13EF}"; - 0xFB00, "\u{0066}\u{0066}"; 0xFB01, "\u{0066}\u{0069}"; - 0xFB02, "\u{0066}\u{006C}"; 0xFB03, "\u{0066}\u{0066}\u{0069}"; - 0xFB04, "\u{0066}\u{0066}\u{006C}"; 0xFB05, "\u{0073}\u{0074}"; - 0xFB06, "\u{0073}\u{0074}"; 0xFB13, "\u{0574}\u{0576}"; - 0xFB14, "\u{0574}\u{0565}"; 0xFB15, "\u{0574}\u{056B}"; - 0xFB16, "\u{057E}\u{0576}"; 0xFB17, "\u{0574}\u{056D}"; - 0xFF21, "\u{FF41}"; 0xFF22, "\u{FF42}"; 0xFF23, "\u{FF43}"; - 0xFF24, "\u{FF44}"; 0xFF25, "\u{FF45}"; 0xFF26, "\u{FF46}"; - 0xFF27, "\u{FF47}"; 0xFF28, "\u{FF48}"; 0xFF29, "\u{FF49}"; - 0xFF2A, "\u{FF4A}"; 0xFF2B, "\u{FF4B}"; 0xFF2C, "\u{FF4C}"; - 0xFF2D, "\u{FF4D}"; 0xFF2E, "\u{FF4E}"; 0xFF2F, "\u{FF4F}"; - 0xFF30, "\u{FF50}"; 0xFF31, "\u{FF51}"; 0xFF32, "\u{FF52}"; - 0xFF33, "\u{FF53}"; 0xFF34, "\u{FF54}"; 0xFF35, "\u{FF55}"; - 0xFF36, "\u{FF56}"; 0xFF37, "\u{FF57}"; 0xFF38, "\u{FF58}"; - 0xFF39, "\u{FF59}"; 0xFF3A, "\u{FF5A}"; 0x10400, "\u{10428}"; - 0x10401, "\u{10429}"; 0x10402, "\u{1042A}"; 0x10403, "\u{1042B}"; - 0x10404, "\u{1042C}"; 0x10405, "\u{1042D}"; 0x10406, "\u{1042E}"; - 0x10407, "\u{1042F}"; 0x10408, "\u{10430}"; 0x10409, "\u{10431}"; - 0x1040A, "\u{10432}"; 0x1040B, "\u{10433}"; 0x1040C, "\u{10434}"; - 0x1040D, "\u{10435}"; 0x1040E, "\u{10436}"; 0x1040F, "\u{10437}"; - 0x10410, "\u{10438}"; 0x10411, "\u{10439}"; 0x10412, "\u{1043A}"; - 0x10413, "\u{1043B}"; 0x10414, "\u{1043C}"; 0x10415, "\u{1043D}"; - 0x10416, "\u{1043E}"; 0x10417, "\u{1043F}"; 0x10418, "\u{10440}"; - 0x10419, "\u{10441}"; 0x1041A, "\u{10442}"; 0x1041B, "\u{10443}"; - 0x1041C, "\u{10444}"; 0x1041D, "\u{10445}"; 0x1041E, "\u{10446}"; - 0x1041F, "\u{10447}"; 0x10420, "\u{10448}"; 0x10421, "\u{10449}"; - 0x10422, "\u{1044A}"; 0x10423, "\u{1044B}"; 0x10424, "\u{1044C}"; - 0x10425, "\u{1044D}"; 0x10426, "\u{1044E}"; 0x10427, "\u{1044F}"; - 0x104B0, "\u{104D8}"; 0x104B1, "\u{104D9}"; 0x104B2, "\u{104DA}"; - 0x104B3, "\u{104DB}"; 0x104B4, "\u{104DC}"; 0x104B5, "\u{104DD}"; - 0x104B6, "\u{104DE}"; 0x104B7, "\u{104DF}"; 0x104B8, "\u{104E0}"; - 0x104B9, "\u{104E1}"; 0x104BA, "\u{104E2}"; 0x104BB, "\u{104E3}"; - 0x104BC, "\u{104E4}"; 0x104BD, "\u{104E5}"; 0x104BE, "\u{104E6}"; - 0x104BF, "\u{104E7}"; 0x104C0, "\u{104E8}"; 0x104C1, "\u{104E9}"; - 0x104C2, "\u{104EA}"; 0x104C3, "\u{104EB}"; 0x104C4, "\u{104EC}"; - 0x104C5, "\u{104ED}"; 0x104C6, "\u{104EE}"; 0x104C7, "\u{104EF}"; - 0x104C8, "\u{104F0}"; 0x104C9, "\u{104F1}"; 0x104CA, "\u{104F2}"; - 0x104CB, "\u{104F3}"; 0x104CC, "\u{104F4}"; 0x104CD, "\u{104F5}"; - 0x104CE, "\u{104F6}"; 0x104CF, "\u{104F7}"; 0x104D0, "\u{104F8}"; - 0x104D1, "\u{104F9}"; 0x104D2, "\u{104FA}"; 0x104D3, "\u{104FB}"; - 0x10570, "\u{10597}"; 0x10571, "\u{10598}"; 0x10572, "\u{10599}"; - 0x10573, "\u{1059A}"; 0x10574, "\u{1059B}"; 0x10575, "\u{1059C}"; - 0x10576, "\u{1059D}"; 0x10577, "\u{1059E}"; 0x10578, "\u{1059F}"; - 0x10579, "\u{105A0}"; 0x1057A, "\u{105A1}"; 0x1057C, "\u{105A3}"; - 0x1057D, "\u{105A4}"; 0x1057E, "\u{105A5}"; 0x1057F, "\u{105A6}"; - 0x10580, "\u{105A7}"; 0x10581, "\u{105A8}"; 0x10582, "\u{105A9}"; - 0x10583, "\u{105AA}"; 0x10584, "\u{105AB}"; 0x10585, "\u{105AC}"; - 0x10586, "\u{105AD}"; 0x10587, "\u{105AE}"; 0x10588, "\u{105AF}"; - 0x10589, "\u{105B0}"; 0x1058A, "\u{105B1}"; 0x1058C, "\u{105B3}"; - 0x1058D, "\u{105B4}"; 0x1058E, "\u{105B5}"; 0x1058F, "\u{105B6}"; - 0x10590, "\u{105B7}"; 0x10591, "\u{105B8}"; 0x10592, "\u{105B9}"; - 0x10594, "\u{105BB}"; 0x10595, "\u{105BC}"; 0x10C80, "\u{10CC0}"; - 0x10C81, "\u{10CC1}"; 0x10C82, "\u{10CC2}"; 0x10C83, "\u{10CC3}"; - 0x10C84, "\u{10CC4}"; 0x10C85, "\u{10CC5}"; 0x10C86, "\u{10CC6}"; - 0x10C87, "\u{10CC7}"; 0x10C88, "\u{10CC8}"; 0x10C89, "\u{10CC9}"; - 0x10C8A, "\u{10CCA}"; 0x10C8B, "\u{10CCB}"; 0x10C8C, "\u{10CCC}"; - 0x10C8D, "\u{10CCD}"; 0x10C8E, "\u{10CCE}"; 0x10C8F, "\u{10CCF}"; - 0x10C90, "\u{10CD0}"; 0x10C91, "\u{10CD1}"; 0x10C92, "\u{10CD2}"; - 0x10C93, "\u{10CD3}"; 0x10C94, "\u{10CD4}"; 0x10C95, "\u{10CD5}"; - 0x10C96, "\u{10CD6}"; 0x10C97, "\u{10CD7}"; 0x10C98, "\u{10CD8}"; - 0x10C99, "\u{10CD9}"; 0x10C9A, "\u{10CDA}"; 0x10C9B, "\u{10CDB}"; - 0x10C9C, "\u{10CDC}"; 0x10C9D, "\u{10CDD}"; 0x10C9E, "\u{10CDE}"; - 0x10C9F, "\u{10CDF}"; 0x10CA0, "\u{10CE0}"; 0x10CA1, "\u{10CE1}"; - 0x10CA2, "\u{10CE2}"; 0x10CA3, "\u{10CE3}"; 0x10CA4, "\u{10CE4}"; - 0x10CA5, "\u{10CE5}"; 0x10CA6, "\u{10CE6}"; 0x10CA7, "\u{10CE7}"; - 0x10CA8, "\u{10CE8}"; 0x10CA9, "\u{10CE9}"; 0x10CAA, "\u{10CEA}"; - 0x10CAB, "\u{10CEB}"; 0x10CAC, "\u{10CEC}"; 0x10CAD, "\u{10CED}"; - 0x10CAE, "\u{10CEE}"; 0x10CAF, "\u{10CEF}"; 0x10CB0, "\u{10CF0}"; - 0x10CB1, "\u{10CF1}"; 0x10CB2, "\u{10CF2}"; 0x10D50, "\u{10D70}"; - 0x10D51, "\u{10D71}"; 0x10D52, "\u{10D72}"; 0x10D53, "\u{10D73}"; - 0x10D54, "\u{10D74}"; 0x10D55, "\u{10D75}"; 0x10D56, "\u{10D76}"; - 0x10D57, "\u{10D77}"; 0x10D58, "\u{10D78}"; 0x10D59, "\u{10D79}"; - 0x10D5A, "\u{10D7A}"; 0x10D5B, "\u{10D7B}"; 0x10D5C, "\u{10D7C}"; - 0x10D5D, "\u{10D7D}"; 0x10D5E, "\u{10D7E}"; 0x10D5F, "\u{10D7F}"; - 0x10D60, "\u{10D80}"; 0x10D61, "\u{10D81}"; 0x10D62, "\u{10D82}"; - 0x10D63, "\u{10D83}"; 0x10D64, "\u{10D84}"; 0x10D65, "\u{10D85}"; - 0x118A0, "\u{118C0}"; 0x118A1, "\u{118C1}"; 0x118A2, "\u{118C2}"; - 0x118A3, "\u{118C3}"; 0x118A4, "\u{118C4}"; 0x118A5, "\u{118C5}"; - 0x118A6, "\u{118C6}"; 0x118A7, "\u{118C7}"; 0x118A8, "\u{118C8}"; - 0x118A9, "\u{118C9}"; 0x118AA, "\u{118CA}"; 0x118AB, "\u{118CB}"; - 0x118AC, "\u{118CC}"; 0x118AD, "\u{118CD}"; 0x118AE, "\u{118CE}"; - 0x118AF, "\u{118CF}"; 0x118B0, "\u{118D0}"; 0x118B1, "\u{118D1}"; - 0x118B2, "\u{118D2}"; 0x118B3, "\u{118D3}"; 0x118B4, "\u{118D4}"; - 0x118B5, "\u{118D5}"; 0x118B6, "\u{118D6}"; 0x118B7, "\u{118D7}"; - 0x118B8, "\u{118D8}"; 0x118B9, "\u{118D9}"; 0x118BA, "\u{118DA}"; - 0x118BB, "\u{118DB}"; 0x118BC, "\u{118DC}"; 0x118BD, "\u{118DD}"; - 0x118BE, "\u{118DE}"; 0x118BF, "\u{118DF}"; 0x16E40, "\u{16E60}"; - 0x16E41, "\u{16E61}"; 0x16E42, "\u{16E62}"; 0x16E43, "\u{16E63}"; - 0x16E44, "\u{16E64}"; 0x16E45, "\u{16E65}"; 0x16E46, "\u{16E66}"; - 0x16E47, "\u{16E67}"; 0x16E48, "\u{16E68}"; 0x16E49, "\u{16E69}"; - 0x16E4A, "\u{16E6A}"; 0x16E4B, "\u{16E6B}"; 0x16E4C, "\u{16E6C}"; - 0x16E4D, "\u{16E6D}"; 0x16E4E, "\u{16E6E}"; 0x16E4F, "\u{16E6F}"; - 0x16E50, "\u{16E70}"; 0x16E51, "\u{16E71}"; 0x16E52, "\u{16E72}"; - 0x16E53, "\u{16E73}"; 0x16E54, "\u{16E74}"; 0x16E55, "\u{16E75}"; - 0x16E56, "\u{16E76}"; 0x16E57, "\u{16E77}"; 0x16E58, "\u{16E78}"; - 0x16E59, "\u{16E79}"; 0x16E5A, "\u{16E7A}"; 0x16E5B, "\u{16E7B}"; - 0x16E5C, "\u{16E7C}"; 0x16E5D, "\u{16E7D}"; 0x16E5E, "\u{16E7E}"; - 0x16E5F, "\u{16E7F}"; 0x1E900, "\u{1E922}"; 0x1E901, "\u{1E923}"; - 0x1E902, "\u{1E924}"; 0x1E903, "\u{1E925}"; 0x1E904, "\u{1E926}"; - 0x1E905, "\u{1E927}"; 0x1E906, "\u{1E928}"; 0x1E907, "\u{1E929}"; - 0x1E908, "\u{1E92A}"; 0x1E909, "\u{1E92B}"; 0x1E90A, "\u{1E92C}"; - 0x1E90B, "\u{1E92D}"; 0x1E90C, "\u{1E92E}"; 0x1E90D, "\u{1E92F}"; - 0x1E90E, "\u{1E930}"; 0x1E90F, "\u{1E931}"; 0x1E910, "\u{1E932}"; - 0x1E911, "\u{1E933}"; 0x1E912, "\u{1E934}"; 0x1E913, "\u{1E935}"; - 0x1E914, "\u{1E936}"; 0x1E915, "\u{1E937}"; 0x1E916, "\u{1E938}"; - 0x1E917, "\u{1E939}"; 0x1E918, "\u{1E93A}"; 0x1E919, "\u{1E93B}"; - 0x1E91A, "\u{1E93C}"; 0x1E91B, "\u{1E93D}"; 0x1E91C, "\u{1E93E}"; - 0x1E91D, "\u{1E93F}"; 0x1E91E, "\u{1E940}"; 0x1E91F, "\u{1E941}"; - 0x1E920, "\u{1E942}"; 0x1E921, "\u{1E943}"|] diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 8078af6431..769222781f 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -67,7 +67,7 @@ and inline ~(config : Config.t) ~resolve l = let content = source inline_text_only c in [ Renderer.Inline.Code_span content ] | Math s -> - (* Since CommonMark doesn't support Math's, we just treat it as code. Maybe could use Ext_math_block or Ext_math_display *) + (* Since CommonMark doesn't support Math's, we treat it a inline code *) [ Renderer.Inline.Code_span [ s ] ] | Raw_markup (target, content) -> ( match Astring.String.Ascii.lowercase target with @@ -115,24 +115,18 @@ let rec block ~config ~resolve l = (* CommonMark treats paragraph as a block, to align the behavior with other generators such as HTML, we add a blank line after it *) let break = Renderer.Block.Blank_line in [ paragraph_block; break ] - | List (typ, l) -> - let list_type = - match typ with - | Ordered -> Renderer.Block.Ordered - | Unordered -> Renderer.Block.Unordered - in - let list_items = + | List (type_, l) -> + let items = List.map (fun items -> let block = block ~config ~resolve items in - let blocks = Renderer.Block.Blocks block in - blocks) + Renderer.Block.Blocks block) l in [ - (* TODO: Do we need the list ~tight:false based on surrounding content or can we always be ~tight:true? *) - Renderer.Block.List - { type_ = list_type; tight = true; items = list_items }; + (match type_ with + | Ordered -> Renderer.Block.Ordered_list items + | Unordered -> Renderer.Block.Unordered_list items); ] | Inline i -> let inlines = Renderer.Inline.Inlines (inline ~config ~resolve i) in @@ -173,7 +167,8 @@ let rec block ~config ~resolve l = | Raw_markup (target, content) -> ( match Astring.String.Ascii.lowercase target with | "html" -> - let block_lines = Renderer.Block_line.list_of_string content in + (* TODO: Make sure block_line_of_string is needed *) + let block_lines = Renderer.block_line_of_string content in [ Renderer.Block.Html_block block_lines ] | another_lang -> (* TODO: Is this correct? *) @@ -212,6 +207,7 @@ let rec block ~config ~resolve l = in List.concat_map one l +(* TODO: Use Block.Table instead of operating on text *) and block_table t = let rows_data : (string * [ `Data | `Header ]) list list = match t.data with diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index 3d98893a3c..71171db6e3 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -1,189 +1,34 @@ -(* TODO: What can we do with Uchar / Uset and Umap? *) -(* TODO: What can we do with Ascii? *) - -module Uset = struct - include Set.Make (Uchar) - let of_array = - let add acc u = add (Uchar.unsafe_of_int u) acc in - Array.fold_left add empty -end - -module Umap = struct - include Map.Make (Uchar) - let of_array = - let add acc (u, f) = add (Uchar.unsafe_of_int u) f acc in - Array.fold_left add empty -end - -let case_fold_umap = Umap.of_array Data_uchar.case_fold -let unicode_case_fold u = Umap.find_opt u case_fold_umap -let punctuation_uset = Uset.of_array Data_uchar.punctuation -let is_unicode_punctuation u = Uset.mem u punctuation_uset - -module Ascii = struct - let is_control = function '\x00' .. '\x1F' | '\x7F' -> true | _ -> false - let is_letter = function 'a' .. 'z' | 'A' .. 'Z' -> true | _ -> false - let is_upper = function 'A' .. 'Z' -> true | _ -> false - let is_lower = function 'a' .. 'z' -> true | _ -> false - let is_digit = function '0' .. '9' -> true | _ -> false - let is_hex_digit = function - | '0' .. '9' | 'A' .. 'F' | 'a' .. 'f' -> true - | _ -> false - - let hex_digit_to_int = function - | '0' .. '9' as c -> Char.code c - 0x30 - | 'A' .. 'F' as c -> Char.code c - 0x37 - | 'a' .. 'f' as c -> Char.code c - 0x57 - | _ -> assert false - - let is_alphanum = function - | 'a' .. 'z' | 'A' .. 'Z' | '0' .. '9' -> true - | _ -> false - - let is_white = function - | '\x20' | '\x09' | '\x0A' | '\x0B' | '\x0C' | '\x0D' -> true - | _ -> false - - let is_punct = function - (* https://spec.commonmark.org/current/#ascii-punctuation-character *) - | '!' | '\"' | '#' | '$' | '%' | '&' | '\'' | '(' | ')' | '*' | '+' | ',' - | '-' | '.' | '/' | ':' | ';' | '<' | '=' | '>' | '?' | '@' | '[' | '\\' - | ']' | '^' | '_' | '`' | '{' | '|' | '}' | '~' -> - true - | _ -> false - - let is_blank = function ' ' | '\t' -> true | _ -> false - - let caseless_starts_with ~prefix s = - let get = String.get in - let len_a = String.length prefix in - let len_s = String.length s in - if len_a > len_s then false - else - let max_idx_a = len_a - 1 in - let rec loop s i max = - if i > max then true - else - let c = - match get s i with - | 'A' .. 'Z' as c -> Char.(unsafe_chr (code c + 32)) - | c -> c - in - if get prefix i <> c then false else loop s (i + 1) max - in - loop s 0 max_idx_a +let is_control = function '\x00' .. '\x1F' | '\x7F' -> true | _ -> false - let match' ~sub s ~start = - (* assert (start + String.length sub - 1 < String.length s) *) - try - for i = 0 to String.length sub - 1 do - if s.[start + i] <> sub.[i] then raise_notrace Exit - done; - true - with Exit -> false - - let caseless_match ~sub s ~start = - (* assert (start + String.length sub - 1 < String.length s) *) - try - for i = 0 to String.length sub - 1 do - let c = - match s.[start + i] with - | 'A' .. 'Z' as c -> Char.(unsafe_chr (code c + 32)) - | c -> c - in - if c <> sub.[i] then raise_notrace Exit - done; - true - with Exit -> false - - let lowercase_sub s first len = - let b = Bytes.create len in - for i = 0 to len - 1 do - let c = - match s.[first + i] with - | 'A' .. 'Z' as c -> Char.(unsafe_chr (code c + 32)) - | c -> c - in - Bytes.set b i c - done; - Bytes.unsafe_to_string b -end +let is_letter = function 'a' .. 'z' | 'A' .. 'Z' -> true | _ -> false -module Match = struct - let rec first_non_blank s ~last ~start = - if start > last then last + 1 - else - match s.[start] with - | ' ' | '\t' -> first_non_blank s ~last ~start:(start + 1) - | _ -> start - - let autolink_email s ~last ~start = - (* https://spec.commonmark.org/current/#email-address - Via the ABNF "<" email ">" with email defined by: - https://html.spec.whatwg.org/multipage/input.html#valid-e-mail-address *) - let is_atext_plus_dot = function - | 'a' .. 'z' - | 'A' .. 'Z' - | '0' .. '9' - | '!' | '#' | '$' | '%' | '&' | '\'' | '*' | '+' | '-' | '/' | '=' | '?' - | '^' | '_' | '`' | '{' | '|' | '}' | '~' | '.' -> - true - | _ -> false - in - let is_let_dig = Ascii.is_alphanum in - let is_let_dig_hyp c = Ascii.is_alphanum c || c = '-' in - let rec label_seq s last k = - let rec loop s last c k = - if k > last then None - else if is_let_dig_hyp s.[k] && c <= 63 then loop s last (c + 1) (k + 1) - else if c > 63 || not (is_let_dig s.[k - 1]) then None - else - match s.[k] with - | '>' -> Some k - | '.' -> label_seq s last (k + 1) - | _ -> None - in - if k > last || not (is_let_dig s.[k]) then None else loop s last 1 (k + 1) - in - let rec atext_seq s last k = - if k > last then None - else if is_atext_plus_dot s.[k] then atext_seq s last (k + 1) - else if s.[k] = '@' && is_atext_plus_dot s.[k - 1] then - label_seq s last (k + 1) - else None - in - if start > last || s.[start] <> '<' then None - else atext_seq s last (start + 1) -end +let is_digit = function '0' .. '9' -> true | _ -> false -module Block_line = struct - let _list_of_string flush s = - (* cuts [s] on newlines *) - let rec loop s acc max start k = - if k > max then List.rev (flush s start max acc) - else if not (s.[k] = '\n' || s.[k] = '\r') then - loop s acc max start (k + 1) - else - let acc = flush s start (k - 1) acc in - let next = k + 1 in - let start = - if s.[k] = '\r' && next <= max && s.[next] = '\n' then next + 1 - else next - in - loop s acc max start start - in - loop s [] (String.length s - 1) 0 0 +let is_alphanum = function + | 'a' .. 'z' | 'A' .. 'Z' | '0' .. '9' -> true + | _ -> false +let block_line_of_string s = let flush s start last acc = let sub = String.sub s start (last - start + 1) in sub :: acc + in + (* cuts [s] on newlines *) + let rec loop s acc max start k = + if k > max then List.rev (flush s start max acc) + else if not (s.[k] = '\n' || s.[k] = '\r') then loop s acc max start (k + 1) + else + let acc = flush s start (k - 1) acc in + let next = k + 1 in + let start = + if s.[k] = '\r' && next <= max && s.[next] = '\n' then next + 1 + else next + in + loop s acc max start start + in + loop s [] (String.length s - 1) 0 0 - let list_of_string s = _list_of_string flush s - - type tight = string -end - -type label = { key : string; text : Block_line.tight list } +type label = { key : string; text : string list } module Link_definition = struct (* let default_layout = @@ -200,7 +45,7 @@ module Link_definition = struct label : label option; defined_label : label option; dest : string option; - title : Block_line.tight list option; + title : string list option; } let make ?defined_label ?label ?dest ?title () = @@ -217,14 +62,14 @@ end module Inline = struct type t = | Break - | Code_span of string list - | Emphasis of t - | Image of link | Inlines of t list - | Link of link - | Raw_html of string list - | Strong_emphasis of t - | Text of string + | Text of string (* plain text *) + | Code_span of string list (* `code` *) + | Emphasis of t (* *emphasis* *) + | Strong_emphasis of t (* **strong emphasis** *) + | Image of link (* ![alt text](url) *) + | Link of link (* [link text](url) *) + | Raw_html of string list (* raw html *) and link = { text : t; reference : Link_definition.t } let is_empty = function Text "" | Inlines [] -> true | _ -> false @@ -237,26 +82,10 @@ module Block = struct type id = [ `Auto of string | `Id of string ] type heading = { level : int; inline : Inline.t; id : id option } - type t = - | Blank_line - | Blocks of t list - | Code_block of code_block - | Heading of heading - | Html_block of string list - | Link_reference_definition of Link_definition.t - | List of list' - | Paragraph of Inline.t - and list' = { type_ : list_type; tight : bool; items : t list } - let empty = Blocks [] - - (* Extensions *) - module Table = struct - type align = [ `Left | `Center | `Right ] - type sep = align option + type sep = [ `Left | `Center | `Right ] option type row = [ `Header of Inline.t list | `Sep of sep list | `Data of Inline.t list ] - type t = { col_count : int; rows : row list } let col_count rows = @@ -302,14 +131,24 @@ module Block = struct in loop [] cs end + + type t = + | Blank_line + | Blocks of t list + | Code_block of code_block (* ``` xxx ``` *) + | Heading of heading (* # heading *) + | Html_block of string list (* raw html *) + | Unordered_list of t list (* - item *) + | Ordered_list of t list (* 1. item *) + | Paragraph of Inline.t (* paragraph *) + | Table of Table.t + let empty = Blocks [] end type doc = Block.t -(* Heterogeneous dictionaries *) - -module Dict = struct - (* Type identifiers, can be deleted once we require 5.1 *) +module Heterogeneous_dict = struct + (* Type identifiers *) module Type = struct type (_, _) eq = Equal : ('a, 'a) eq module Id = struct @@ -362,25 +201,29 @@ type t = { block : block; } -and context = { renderer : t; mutable state : Dict.t; b : Buffer.t } +and context = { + renderer : t; + mutable state : Heterogeneous_dict.t; + b : Buffer.t; +} and inline = context -> Inline.t -> unit and block = context -> Block.t -> unit module Context = struct type t = context - let make renderer b = { renderer; b; state = Dict.empty } + let make renderer b = { renderer; b; state = Heterogeneous_dict.empty } let buffer c = c.b module State = struct - type 'a t = 'a Dict.key - let make = Dict.key - let find c st = Dict.find st c.state - let get c st = Option.get (Dict.find st c.state) + type 'a t = 'a Heterogeneous_dict.key + let make = Heterogeneous_dict.key + let find c st = Heterogeneous_dict.find st c.state + let get c st = Option.get (Heterogeneous_dict.find st c.state) let set c st = function - | None -> c.state <- Dict.remove st c.state - | Some s -> c.state <- Dict.add st s c.state + | None -> c.state <- Heterogeneous_dict.remove st c.state + | Some s -> c.state <- Heterogeneous_dict.add st s c.state end let init c d = c.renderer.init_context c d @@ -439,7 +282,7 @@ let buffer_add_escaped_string ?(esc_ctrl = true) b cs s = flush b max start i; buffer_add_bslash_esc b c; loop b s max next next) - else if esc_ctrl && Ascii.is_control c then ( + else if esc_ctrl && is_control c then ( flush b max start i; buffer_add_dec_esc b c; loop b s max next next) @@ -460,7 +303,7 @@ let buffer_add_escaped_text b s = | _ -> false in let esc_amp s max next = - next <= max && (Ascii.is_letter s.[next] || s.[next] = '#') + next <= max && (is_letter s.[next] || s.[next] = '#') in let esc_tilde s max prev next = (not (Char.equal prev '~')) && next <= max && s.[next] = '~' @@ -469,7 +312,7 @@ let buffer_add_escaped_text b s = if i = 0 || i > 9 (* marker has from 1-9 digits *) then false else let k = ref (i - 1) in - while !k >= 0 && Ascii.is_digit s.[!k] do + while !k >= 0 && is_digit s.[!k] do decr k done; !k < 0 @@ -482,7 +325,7 @@ let buffer_add_escaped_text b s = else let next = i + 1 in let c = String.get s i in - if Ascii.is_control c then ( + if is_control c then ( flush b max start i; buffer_add_dec_esc b c; loop b s max next c next) @@ -712,17 +555,6 @@ let html_block c h = indent c; block_lines c h -let link_reference_definition c ld = - newline c; - indent c; - nchars c 0 ' '; - Context.byte c '['; - (match Link_definition.label ld with - | None -> () - | Some label -> escaped_tight_block_lines c esc_link_label label.text); - Context.string c "]:"; - link_definition c ld - let unordered_item c marker i = let before = 0 in let after = 1 in @@ -741,14 +573,9 @@ let ordered_item c num i = pop_indent c; num + 1 -let list c (l : Block.list') = - match l.type_ with - | Unordered -> - let marker = String.make 1 '-' in - List.iter (unordered_item c marker) l.items - | Ordered -> - let start = 1 in - ignore (List.fold_left (ordered_item c) start l.items) +let unordered_list c l = List.iter (unordered_item c "-") l + +let ordered_list c l = ignore (List.fold_left (ordered_item c) 1 l) let paragraph c p = newline c; @@ -757,20 +584,61 @@ let paragraph c p = Context.inline c p; Context.string c "" -let block c b = - match (b : Block.t) with - | Blank_line -> blank_line c "" - | Blocks bs -> List.iter (Context.block c) bs - | Code_block cb -> code_block c cb - | Heading h -> heading c h - | Html_block h -> html_block c h - | Link_reference_definition ld -> link_reference_definition c ld - | List l -> list c l - | Paragraph p -> paragraph c p +(* TODO: This isn't tested *) +let table c t = + let col c i = + Context.byte c '|'; + (* Context.string c before; *) + Context.inline c i (* ; + Context.string c after *) + in + let sep c align = + (* TODO: len is hardcoded, it shouldn't be *) + let len = 1 in + Context.byte c '|'; + match align with + | None -> nchars c len '-' + | Some `Left -> + Context.byte c ':'; + nchars c len '-' + | Some `Center -> + Context.byte c ':'; + nchars c len '-'; + Context.byte c ':' + | Some `Right -> + nchars c len '-'; + Context.byte c ':' + in + let row c (row : Block.Table.row) = + match row with + | `Header cols | `Data cols -> + newline c; + indent c; + if cols = [] then Context.byte c '|' else List.iter (col c) cols; + Context.byte c '|' + | `Sep seps -> + newline c; + indent c; + if seps = [] then Context.byte c '|' else List.iter (sep c) seps; + Context.byte c '|' + in + List.iter (row c) (Block.Table.rows t); + pop_indent c + +let block c = function + | Block.Blank_line -> blank_line c "" + | Block.Blocks bs -> List.iter (Context.block c) bs + | Block.Code_block cb -> code_block c cb + | Block.Heading h -> heading c h + | Block.Html_block h -> html_block c h + | Block.Unordered_list l -> unordered_list c l + | Block.Ordered_list l -> ordered_list c l + | Block.Paragraph p -> paragraph c p + | Block.Table t -> table c t let to_string d = let t = { init_context; inline; block } in let buffer = Buffer.create 1024 in - let c = Context.make t buffer in - Context.doc c d; + let ctx = Context.make t buffer in + Context.doc ctx d; Buffer.contents buffer From 68654bc2755a3d439d5cdd19edf3d3f5237dc94c Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 10:27:17 +0200 Subject: [PATCH 42/53] Simplify Link_definition --- src/markdown2/generator.ml | 33 +++++++++---------------- src/markdown2/renderer.ml | 50 ++++++-------------------------------- 2 files changed, 19 insertions(+), 64 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 769222781f..557eef5766 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -20,7 +20,7 @@ and styled style content = let inlines_as_one_inline = Renderer.Inline.Inlines content in [ Renderer.Inline.Emphasis inlines_as_one_inline ] | `Superscript | `Subscript -> - (* CommonMark doesn't have support for superscript/subscript, render the content as inline *) + (* CommonMark doesn't have support for superscript/subscript, we fallback to inline *) content let entity = function "#45" -> "-" | "gt" -> ">" | e -> "&" ^ e ^ ";" @@ -55,7 +55,7 @@ and inline ~(config : Config.t) ~resolve l = match t.desc with | Text s -> [ Renderer.Inline.Text s ] | Entity s -> - (* In CommonMark, HTML entities are supported directly, so we can just output them as text *) + (* In CommonMark, HTML entities are supported directly, so we can just output them as text. Some markdown parsers may not support some entities. *) [ Renderer.Inline.Text s ] | Linebreak -> [ Renderer.Inline.Break ] | Styled (style, c) -> @@ -98,11 +98,7 @@ and inline_link ~config ~resolve link = | Some href -> let inline_content = inline ~config ~resolve link.content in let link_inline = Renderer.Inline.Inlines inline_content in - let link_definition = Renderer.Link_definition.make ~dest:href () in - let inline_link : Renderer.Inline.link = - { text = link_inline; reference = link_definition } - in - [ Renderer.Inline.Link inline_link ] + [ Renderer.Inline.Link { text = link_inline; url = Some href } ] | None -> [ Renderer.Inline.Code_span (inline_text_only link.content) ] let rec block ~config ~resolve l = @@ -135,7 +131,7 @@ let rec block ~config ~resolve l = | Description l -> let item ({ key; definition; attr = _ } : Types.Description.one) = let term = inline ~config ~resolve key in - (* We extract definition as inline, since it came as "Block". There seems to be no way (in Cmarkit) to make it inline *) + (* We extract definition as inline *) let definition_inline = Renderer.Inline.Text (String.concat ~sep:"" (block_text_only definition)) @@ -167,9 +163,8 @@ let rec block ~config ~resolve l = | Raw_markup (target, content) -> ( match Astring.String.Ascii.lowercase target with | "html" -> - (* TODO: Make sure block_line_of_string is needed *) - let block_lines = Renderer.block_line_of_string content in - [ Renderer.Block.Html_block block_lines ] + let html_block_lines = Renderer.block_line_of_string content in + [ Renderer.Block.Html_block html_block_lines ] | another_lang -> (* TODO: Is this correct? *) let msg = @@ -195,10 +190,7 @@ let rec block ~config ~resolve l = "" in let image : Renderer.Inline.link = - { - text = Renderer.Inline.Text alt; - reference = Renderer.Link_definition.make ~dest (); - } + { text = Renderer.Inline.Text alt; url = Some dest } in [ Renderer.Block.Paragraph @@ -477,13 +469,12 @@ module Page = struct let name = anchor.page.name in let inline_name = Renderer.Inline.Text name in let href = Link.href ~config ~resolve anchor in - let link_definition = - Renderer.Link_definition.make ~dest:href () - in - let inline_link : Renderer.Inline.link = - { text = inline_name; reference = link_definition } + (* TODO: ??? *) + let _ = + [ + Renderer.Inline.Link { text = inline_name; url = Some href }; + ] in - let _ = [ Renderer.Inline.Link inline_link ] in childrens | Anchor _lbl -> childrens) in diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index 71171db6e3..1af33f88b2 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -30,35 +30,6 @@ let block_line_of_string s = type label = { key : string; text : string list } -module Link_definition = struct - (* let default_layout = - { - indent = 0; - angled_dest = false; - before_dest = []; - after_dest = []; - title_open_delim = '\"'; - after_title = []; - } *) - - type t = { - label : label option; - defined_label : label option; - dest : string option; - title : string list option; - } - - let make ?defined_label ?label ?dest ?title () = - let defined_label = - match defined_label with None -> label | Some d -> d - in - { label; defined_label; dest; title } - let label ld = ld.label - let defined_label ld = ld.defined_label - let dest ld = ld.dest - let title ld = ld.title -end - module Inline = struct type t = | Break @@ -69,8 +40,9 @@ module Inline = struct | Strong_emphasis of t (* **strong emphasis** *) | Image of link (* ![alt text](url) *) | Link of link (* [link text](url) *) - | Raw_html of string list (* raw html *) - and link = { text : t; reference : Link_definition.t } + | Raw_html of string list (*
*) + and link = { text : t; url : string option } + (* and reference = { url : string option; title : string list option } *) let is_empty = function Text "" | Inlines [] -> true | _ -> false end @@ -98,7 +70,7 @@ module Block = struct loop 0 rows let make rows = { col_count = col_count rows; rows } - let col_count t = t.col_count + let rows t = t.rows let parse_sep_row cs = @@ -478,22 +450,14 @@ let link_title c open_delim title = escaped_tight_block_lines c escapes lines; Context.byte c close -let link_definition c ld = - (match Link_definition.dest ld with - | None -> () - | Some dest -> escaped_string c esc_parens dest); - if - Option.is_some (Link_definition.dest ld) - && Option.is_some (Link_definition.title ld) - then Context.byte c ' ' (* at least a space is needed *); - link_title c '\"' (Link_definition.title ld) - let link c (l : Inline.link) = Context.byte c '['; Context.inline c l.text; Context.byte c ']'; Context.byte c '('; - link_definition c l.reference; + (match l.url with + | None -> () + | Some dest -> escaped_string c esc_parens dest); Context.byte c ')' let image c l = From 208c85578485de8c8df9509bac4d086e233e7e99 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 12:03:13 +0200 Subject: [PATCH 43/53] Remove all failwith since generator can't fail --- src/markdown2/generator.ml | 28 +++++++--------------------- 1 file changed, 7 insertions(+), 21 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 557eef5766..fbf3d35866 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -74,14 +74,9 @@ and inline ~(config : Config.t) ~resolve l = | "html" -> let block_lines = content in [ Renderer.Inline.Raw_html [ block_lines ] ] - | another_lang -> - (* TODO: Is this correct? *) - let msg = - "Markdown only supports html blocks. There's a raw with " - ^ another_lang - in - (* QUESTION: Should we render an empty block? Can we do something else rather failwith? *) - failwith msg) + | _ -> + (* Markdown only supports html blocks *) + []) in List.concat_map one l @@ -165,19 +160,7 @@ let rec block ~config ~resolve l = | "html" -> let html_block_lines = Renderer.block_line_of_string content in [ Renderer.Block.Html_block html_block_lines ] - | another_lang -> - (* TODO: Is this correct? *) - let msg = - "Markdown only supports html blocks. There's a raw with " - ^ another_lang - in - failwith msg) - | Audio (_target, _alt) -> - (* TODO: Raise a decent error here? Maybe warnings, I only saw assert false *) - failwith "Audio isn't supported in markdown" - | Video (_target, _alt) -> - (* TODO: Raise a decent error here? Maybe warnings, I only saw assert false *) - failwith "Video isn't supported in markdown" + | _ -> (* Markdown only supports html blocks *) []) | Image (target, alt) -> let dest = match (target : Types.Target.t) with @@ -196,6 +179,9 @@ let rec block ~config ~resolve l = Renderer.Block.Paragraph (Renderer.Inline.Inlines [ Renderer.Inline.Image image ]); ] + | Audio (_target, _alt) | Video (_target, _alt) -> + (* Audio and video aren't supported in markdown *) + [] in List.concat_map one l From 375ab5d82a60c4b44c2d557fea36a1f20e7a42df Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 12:40:33 +0200 Subject: [PATCH 44/53] Refactor table rendering to not use Inlines and use Renderer's --- src/markdown2/generator.ml | 138 ++++++++---------------------- src/markdown2/renderer.ml | 25 +++--- test/integration/markdown.t/run.t | 16 ++-- 3 files changed, 57 insertions(+), 122 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index fbf3d35866..437a77c95c 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -122,7 +122,7 @@ let rec block ~config ~resolve l = | Inline i -> let inlines = Renderer.Inline.Inlines (inline ~config ~resolve i) in [ Renderer.Block.Paragraph inlines ] - | Table t -> block_table t + | Table t -> block_table ~config ~resolve t | Description l -> let item ({ key; definition; attr = _ } : Types.Description.one) = let term = inline ~config ~resolve key in @@ -185,113 +185,49 @@ let rec block ~config ~resolve l = in List.concat_map one l -(* TODO: Use Block.Table instead of operating on text *) -and block_table t = - let rows_data : (string * [ `Data | `Header ]) list list = - match t.data with - | [] -> [] - | rows -> - List.map - (fun (row : (Types.Block.t * [ `Data | `Header ]) list) -> - List.map - (fun (content, cell_type) -> - let cell_text = - String.concat ~sep:" " (block_text_only content) - in - (cell_text, cell_type)) - row) - rows +and block_table ~config ~resolve t = + let alignment = function + | Types.Table.Left -> Some `Left + | Types.Table.Center -> Some `Center + | Types.Table.Right -> Some `Right + | Types.Table.Default -> None in - if rows_data = [] then - [ Renderer.Block.Paragraph (Renderer.Inline.Inlines []) ] - else - let max_columns = - List.fold_left - (fun max_cols row -> - let row_cols = List.length row in - if row_cols > max_cols then row_cols else max_cols) - 0 rows_data - in - - let has_header_row = - match rows_data with - | first_row :: _ -> - List.exists (fun (_, cell_type) -> cell_type = `Header) first_row - | [] -> false - in - - let rec make_list n v = if n <= 0 then [] else v :: make_list (n - 1) v in - - let header_cells, content_rows = - match rows_data with - | first_row :: rest when has_header_row -> - (* Pad header cells to match max_columns *) - let padded_header = - let cells = List.map fst first_row in - let missing = max_columns - List.length cells in - if missing > 0 then cells @ make_list missing "" else cells - in - (padded_header, rest) - | _ -> - (* No header - create an empty header matching the max columns *) - (make_list max_columns "", rows_data) - in - - let pad_row row = - let cells = List.map fst row in - let missing = max_columns - List.length cells in - if missing > 0 then cells @ make_list missing "" else cells - in + let convert_cell content = + match content with + | [ { Types.Block.desc = Paragraph p; _ } ] + | [ { Types.Block.desc = Inline p; _ } ] -> + inline ~config ~resolve p + | blocks -> + let text = String.concat ~sep:" " (block_text_only blocks) in + [ Renderer.Inline.Text text ] + in - let header_inline = - let header_text = "| " ^ String.concat ~sep:" | " header_cells ^ " |" in - let header_md = Renderer.Inline.Text header_text in - Renderer.Inline.Inlines [ header_md ] + let convert_row (row : (Types.Block.t * [ `Data | `Header ]) list) = + let cells = + List.map + (fun (content, _) -> Renderer.Inline.Inlines (convert_cell content)) + row in + match row with (_, `Header) :: _ -> `Header cells | _ -> `Data cells + in - (* Create the separator row (based on column alignment) *) - let separator_inline = - let alignments = - if List.length t.align >= max_columns then - (* Take only the first max_columns elements *) - let rec take n lst = - if n <= 0 then [] - else match lst with [] -> [] | h :: t -> h :: take (n - 1) t - in - take max_columns t.align - else - t.align - @ make_list (max_columns - List.length t.align) Types.Table.Default - in - - let separator_cells = - List.map - (fun align -> - match (align : Types.Table.alignment) with - | Left -> ":---" - | Center -> ":---:" - | Right -> "---:" - | Default -> "---") - alignments + match t.data with + | [] -> [ Renderer.Block.Paragraph (Renderer.Inline.Inlines []) ] + | rows -> + let table_rows = List.map convert_row rows in + let separator = `Sep (List.map alignment t.align) in + let rec insert_separator acc = function + | [] -> List.rev acc + | (`Header _ as h) :: (`Data _ :: _ as rest) -> + List.rev (h :: acc) @ [ separator ] @ rest + | (`Header _ as h) :: rest -> insert_separator (h :: acc) rest + | rows -> List.rev acc @ [ separator ] @ rows in - let sep_text = "| " ^ String.concat ~sep:" | " separator_cells ^ " |" in - let sep_md = Renderer.Inline.Text sep_text in - Renderer.Inline.Inlines [ sep_md ] - in - let content_inlines = - List.map - (fun row -> - let cells = pad_row row in - let row_text = "| " ^ String.concat ~sep:" | " cells ^ " |" in - let row_md = Renderer.Inline.Text row_text in - Renderer.Inline.Inlines [ row_md ]) - content_rows - in - List.map - (fun inline -> Renderer.Block.Paragraph inline) - ([ header_inline; separator_inline ] @ content_inlines) + let final_rows = insert_separator [] table_rows in + let table = Renderer.Block.Table.make final_rows in + [ Renderer.Block.Table table ] and items ~config ~resolve l : Renderer.Block.t list = let rec walk_items acc (t : Types.Item.t list) = diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index 1af33f88b2..06cbc9372c 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -548,30 +548,30 @@ let paragraph c p = Context.inline c p; Context.string c "" -(* TODO: This isn't tested *) let table c t = let col c i = Context.byte c '|'; - (* Context.string c before; *) - Context.inline c i (* ; - Context.string c after *) + Context.byte c ' '; + Context.inline c i; + Context.byte c ' ' in let sep c align = - (* TODO: len is hardcoded, it shouldn't be *) - let len = 1 in + let len = 3 in Context.byte c '|'; - match align with + Context.byte c ' '; + (match align with | None -> nchars c len '-' | Some `Left -> Context.byte c ':'; - nchars c len '-' + nchars c (len - 1) '-' | Some `Center -> Context.byte c ':'; - nchars c len '-'; + nchars c (len - 2) '-'; Context.byte c ':' | Some `Right -> - nchars c len '-'; - Context.byte c ':' + nchars c (len - 1) '-'; + Context.byte c ':'); + Context.byte c ' ' in let row c (row : Block.Table.row) = match row with @@ -586,8 +586,7 @@ let table c t = if seps = [] then Context.byte c '|' else List.iter (sep c) seps; Context.byte c '|' in - List.iter (row c) (Block.Table.rows t); - pop_indent c + List.iter (row c) (Block.Table.rows t) let block c = function | Block.Blank_line -> blank_line c "" diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 862a73f097..5a1044abda 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -169,17 +169,17 @@ ##### Explicit syntax - \| Header 1 \| Header 2 \| - \| --- \| --- \| - \| Cell 1 \| Cell 2 \| - \| Cell 3 \| Cell 4 \| + | Header 1 | Header 2 | + | --- | --- | + | Cell 1 | Cell 2 | + | Cell 3 | Cell 4 | ##### Light syntax - \| Header 1 \| Header 2 \| - \| --- \| --- \| - \| Cell 1 \| Cell 2 \| - \| Cell 3 \| Cell 4 \| + | Header 1 | Header 2 | + | --- | --- | + | Cell 1 | Cell 2 | + | Cell 3 | Cell 4 | #### HTML From 79e30b440d180123140c35bbbe1802c4a70fa87c Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 12:46:55 +0200 Subject: [PATCH 45/53] Add atribution to cmarkit under ISC --- src/markdown2/renderer.ml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index 06cbc9372c..a2bcd3949f 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -1,3 +1,5 @@ +(* This module is based on cmarkit (https://github.com/dbuenzli/cmarkit) which is distributed under the ISC License. *) + let is_control = function '\x00' .. '\x1F' | '\x7F' -> true | _ -> false let is_letter = function 'a' .. 'z' | 'A' .. 'Z' -> true | _ -> false From 4ab2f94f607b7d629014d5841a99422a86cfcd62 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 13:23:23 +0200 Subject: [PATCH 46/53] Resolve issues/doubts for generation --- src/markdown2/generator.ml | 15 +++++---------- src/markdown2/renderer.ml | 1 - 2 files changed, 5 insertions(+), 11 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 437a77c95c..8557db8ae7 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -162,18 +162,14 @@ let rec block ~config ~resolve l = [ Renderer.Block.Html_block html_block_lines ] | _ -> (* Markdown only supports html blocks *) []) | Image (target, alt) -> - let dest = + let url = match (target : Types.Target.t) with - | External url -> url - | Internal (Resolved uri) -> - let url = Link.href ~config ~resolve uri in - url - | Internal Unresolved -> - (* TODO: What's unresolved? A non-existing page/link? *) - "" + | External url -> Some url + | Internal (Resolved uri) -> Some (Link.href ~config ~resolve uri) + | Internal Unresolved -> None in let image : Renderer.Inline.link = - { text = Renderer.Inline.Text alt; url = Some dest } + { text = Renderer.Inline.Text alt; url } in [ Renderer.Block.Paragraph @@ -347,7 +343,6 @@ module Page = struct and subpages ~config subpages = List.map (include_ ~config) subpages and page ~config p = - (* TODO: disambiguate the page? *) let subpages = subpages ~config @@ Doctree.Subpages.compute p in let resolve = Link.Current p.url in let i = Doctree.Shift.compute ~on_sub p.items in diff --git a/src/markdown2/renderer.ml b/src/markdown2/renderer.ml index a2bcd3949f..b471433be7 100644 --- a/src/markdown2/renderer.ml +++ b/src/markdown2/renderer.ml @@ -44,7 +44,6 @@ module Inline = struct | Link of link (* [link text](url) *) | Raw_html of string list (*
*) and link = { text : t; url : string option } - (* and reference = { url : string option; title : string list option } *) let is_empty = function Text "" | Inlines [] -> true | _ -> false end From 1893edf49349ffd155d2cf4e2380084a3d7d1c6b Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 13:23:52 +0200 Subject: [PATCH 47/53] Implement source_page in markdown --- src/markdown2/generator.ml | 44 +++++------------- src/odoc/bin/main.ml | 1 + test/sources/markdown_source.t/example.ml | 23 ++++++++++ test/sources/markdown_source.t/run.t | 46 +++++++++++++++++++ test/sources/markdown_source.t/simple_test.ml | 1 + 5 files changed, 83 insertions(+), 32 deletions(-) create mode 100644 test/sources/markdown_source.t/example.ml create mode 100644 test/sources/markdown_source.t/run.t create mode 100644 test/sources/markdown_source.t/simple_test.ml diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 8557db8ae7..145d9ba531 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -357,47 +357,27 @@ module Page = struct Markdown_page.make ~config ~url:p.url doc subpages and source_page ~config sp = - (* TODO: source_page isn't tested in markdown2 *) let { Types.Source_page.url; contents; _ } = sp in let resolve = Link.Current sp.url in let title = url.Url.Path.name in let header = items ~config ~resolve (Doctree.PageTitle.render_src_title sp) in - let markdown_of_doc ~config ~resolve docs = - let rec doc_to_markdown doc = + let extract_source_text docs = + let rec doc_to_text doc = match doc with - | Types.Source_page.Plain_code s -> - let plain_code = - Renderer.Block.Code_block { info_string = None; code = [ s ] } - in - [ plain_code ] - | Tagged_code (info, docs) -> ( - let childrens = List.concat_map doc_to_markdown docs in - match info with - | Syntax tok -> - let syntax = - Renderer.Block.Code_block - { info_string = Some tok; code = [ tok ] } - in - [ syntax; Renderer.Block.Blocks childrens ] - | Link { documentation = _; implementation = None } -> childrens - | Link { documentation = _; implementation = Some anchor } -> - let name = anchor.page.name in - let inline_name = Renderer.Inline.Text name in - let href = Link.href ~config ~resolve anchor in - (* TODO: ??? *) - let _ = - [ - Renderer.Inline.Link { text = inline_name; url = Some href }; - ] - in - childrens - | Anchor _lbl -> childrens) + | Types.Source_page.Plain_code s -> s + | Tagged_code (_, docs) -> + String.concat ~sep:"" (List.map doc_to_text docs) in - List.concat_map doc_to_markdown docs + String.concat ~sep:"" (List.map doc_to_text docs) in - let doc = header @ markdown_of_doc ~config ~resolve contents in + let source_text = extract_source_text contents in + let source_block = + Renderer.Block.Code_block + { info_string = Some "ocaml"; code = [ source_text ] } + in + let doc = header @ [ source_block ] in Markdown_page.make_src ~config ~url title doc end diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index eee8939f61..120189771d 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1769,6 +1769,7 @@ let () = Indexing.(cmd, info ~docs:section_pipeline); Sidebar.(cmd, info ~docs:section_pipeline); Odoc_markdown_cmd.generate ~docs:section_pipeline; + Odoc_markdown_cmd.generate_source ~docs:section_pipeline; Odoc_manpage.generate ~docs:section_generators; Odoc_latex.generate ~docs:section_generators; Odoc_html_url.(cmd, info ~docs:section_support); diff --git a/test/sources/markdown_source.t/example.ml b/test/sources/markdown_source.t/example.ml new file mode 100644 index 0000000000..f70c9b112b --- /dev/null +++ b/test/sources/markdown_source.t/example.ml @@ -0,0 +1,23 @@ +type example_type = int + +module ExampleModule = struct + type inner_type = string + + (** This is a documented function *) + let example_function x = x + 1 + + let another_function s = String.length s +end + +(** This is a documented value *) +let global_value = 42 + +(** This function demonstrates pattern matching *) +let pattern_match = function 0 -> "zero" | 1 -> "one" | _ -> "many" + +exception CustomException of string + +class example_class = + object + method greet name = "Hello, " ^ name + end diff --git a/test/sources/markdown_source.t/run.t b/test/sources/markdown_source.t/run.t new file mode 100644 index 0000000000..f535787cdb --- /dev/null +++ b/test/sources/markdown_source.t/run.t @@ -0,0 +1,46 @@ +Test compile-impl with markdown source generation: + + $ cat simple_test.ml + let x = 42 + +Compile the OCaml source file: + + $ ocamlc -c simple_test.ml -bin-annot + +Compile the implementation with source-id: + + $ odoc compile-impl -I . --source-id src/simple_test.ml simple_test.cmt + +Compile the interface documentation: + + $ odoc compile -I . simple_test.cmt + +Link both documentation and implementation: + + $ odoc link -I . simple_test.odoc + $ odoc link -I . impl-simple_test.odoc + +Generate markdown documentation: + + $ odoc markdown-generate simple_test.odocl -o markdown + +Generate markdown source documentation: + + $ odoc markdown-generate-source --impl impl-simple_test.odocl -o markdown simple_test.ml + +Check that markdown files were generated: + + $ find markdown -name "*.md" | sort + markdown/Simple_test.md + markdown/src/simple_test.ml.md + +Check the generated markdown source file: + + $ cat markdown/src/simple_test.ml.md + + # Source file `simple_test.ml` + + ```ocaml + let x = 42 + + ``` diff --git a/test/sources/markdown_source.t/simple_test.ml b/test/sources/markdown_source.t/simple_test.ml new file mode 100644 index 0000000000..7fecab12d4 --- /dev/null +++ b/test/sources/markdown_source.t/simple_test.ml @@ -0,0 +1 @@ +let x = 42 From 3a27306f8195cbd00210004d5be8b4de14724373 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 13:37:20 +0200 Subject: [PATCH 48/53] Add trimming to remove eof newline --- src/markdown2/generator.ml | 12 ++++++------ test/sources/markdown_source.t/run.t | 1 - test/sources/markdown_source.t/simple_test.re | 1 + 3 files changed, 7 insertions(+), 7 deletions(-) create mode 100644 test/sources/markdown_source.t/simple_test.re diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 145d9ba531..64f63a32a7 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -364,18 +364,18 @@ module Page = struct items ~config ~resolve (Doctree.PageTitle.render_src_title sp) in let extract_source_text docs = - let rec doc_to_text doc = - match doc with - | Types.Source_page.Plain_code s -> s + let rec doc_to_text span = + match (span : Types.Source_page.span) with + | Plain_code s -> s | Tagged_code (_, docs) -> String.concat ~sep:"" (List.map doc_to_text docs) in - String.concat ~sep:"" (List.map doc_to_text docs) + + docs |> List.map doc_to_text |> String.concat ~sep:"" |> String.trim in - let source_text = extract_source_text contents in let source_block = Renderer.Block.Code_block - { info_string = Some "ocaml"; code = [ source_text ] } + { info_string = Some "ocaml"; code = [ extract_source_text contents ] } in let doc = header @ [ source_block ] in Markdown_page.make_src ~config ~url title doc diff --git a/test/sources/markdown_source.t/run.t b/test/sources/markdown_source.t/run.t index f535787cdb..74646867dd 100644 --- a/test/sources/markdown_source.t/run.t +++ b/test/sources/markdown_source.t/run.t @@ -42,5 +42,4 @@ Check the generated markdown source file: ```ocaml let x = 42 - ``` diff --git a/test/sources/markdown_source.t/simple_test.re b/test/sources/markdown_source.t/simple_test.re new file mode 100644 index 0000000000..fabb92f19d --- /dev/null +++ b/test/sources/markdown_source.t/simple_test.re @@ -0,0 +1 @@ +let x = 42; From fffa0027d3e546edf78979de5c36c8efa94748da Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 13:46:18 +0200 Subject: [PATCH 49/53] Remove dependency on opam --- odoc.opam | 1 - 1 file changed, 1 deletion(-) diff --git a/odoc.opam b/odoc.opam index 68243e9a78..42c0539492 100644 --- a/odoc.opam +++ b/odoc.opam @@ -51,7 +51,6 @@ depends: [ "tyxml" {>= "4.4.0"} "fmt" "crunch" {>= "1.4.1"} - "cmarkit" {>= "0.3.0" & ocaml:version >= "4.14"} "ocamlfind" {with-test} "yojson" {>= "2.1.0" & with-test} "sexplib0" {with-test} From b0cba735c27a729f92f2f807368a86e1abb0a83e Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Fri, 6 Jun 2025 13:47:36 +0200 Subject: [PATCH 50/53] Remove unused code for cppo and random comment --- src/markdown2/odoc_markdown.cppo.ml | 16 ---------------- src/odoc/bin/main.ml | 1 - 2 files changed, 17 deletions(-) delete mode 100644 src/markdown2/odoc_markdown.cppo.ml diff --git a/src/markdown2/odoc_markdown.cppo.ml b/src/markdown2/odoc_markdown.cppo.ml deleted file mode 100644 index 3cb2ba4ed0..0000000000 --- a/src/markdown2/odoc_markdown.cppo.ml +++ /dev/null @@ -1,16 +0,0 @@ -module Config = Config - -#if OCAML_VERSION >= (4, 08, 0) -module Generator = Generator -#else -module Generator = struct - let render (_ : Config.t) _ = failwith "Markdown generation isn't available" - - let filepath (_ : Config.t) _ = failwith "Markdown generation isn't available" - - let items (_ : Config.t) _ = failwith "Markdown generation isn't available" - - let inline (_ : Config.t) _ = failwith "Markdown generation isn't available" -end -#endif - diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 120189771d..a1846cfa11 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -1319,7 +1319,6 @@ module Odoc_markdown_cmd = Make_renderer (struct let render config _sidebar page = Odoc_markdown.Generator.render ~config page - (* QUESTION: Where is this being used? *) let filepath config url = Odoc_markdown.Generator.filepath ~config url let extra_args = From df7f5f17ceaa74ba505567bb0d6269bd39014ba8 Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Wed, 2 Jul 2025 20:53:20 +0200 Subject: [PATCH 51/53] add include in the tests --- test/integration/markdown.t/run.t | 6 ++++++ test/integration/markdown.t/test.mli | 8 ++++++++ 2 files changed, 14 insertions(+) diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index 5a1044abda..c4aa91a2b6 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -53,6 +53,12 @@ ``` module List : sig ... end ``` + ``` + module type X = sig ... end + ``` + ``` + module type T = sig ... end + ``` $ cat markdown/test/Test-List.md diff --git a/test/integration/markdown.t/test.mli b/test/integration/markdown.t/test.mli index 6d1c508a65..2d2731fcf3 100644 --- a/test/integration/markdown.t/test.mli +++ b/test/integration/markdown.t/test.mli @@ -13,3 +13,11 @@ module List : sig val head : 'a t -> 'a option val headExn : 'a t -> 'a end + +module type X = sig + type t = int +end + +module type T = sig + include X +end From 1eaccaee0207880b3d243caa5d5f99d4e7bd9276 Mon Sep 17 00:00:00 2001 From: Jon Ludlam Date: Thu, 3 Jul 2025 00:24:20 +0100 Subject: [PATCH 52/53] Check submodule contents in include tests --- test/integration/markdown.t/run.t | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index c4aa91a2b6..c270ee0fad 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -60,6 +60,18 @@ module type T = sig ... end ``` + $ cat markdown/test/Test-module-type-X.md + + # Module type `Test.X` + + ``` + type t = int + ``` + + $ cat markdown/test/Test-module-type-T.md + + # Module type `Test.T` + $ cat markdown/test/Test-List.md # Module `Test.List` From fcd36d4fd13da59a286a5d1fc52f97650ca3a59e Mon Sep 17 00:00:00 2001 From: David Sancho Moreno Date: Thu, 3 Jul 2025 11:04:31 +0200 Subject: [PATCH 53/53] apply 926cca100c307818e57281c3d40e98f1975f0f95 --- src/markdown2/generator.ml | 8 +++++--- test/integration/markdown.t/run.t | 4 ++++ 2 files changed, 9 insertions(+), 3 deletions(-) diff --git a/src/markdown2/generator.ml b/src/markdown2/generator.ml index 64f63a32a7..d11e3c1ed1 100644 --- a/src/markdown2/generator.ml +++ b/src/markdown2/generator.ml @@ -256,11 +256,13 @@ and items ~config ~resolve l : Renderer.Block.t list = anchor = _anchor; source_anchor = _source_anchor; doc; - content = { summary = _summary; status = _status; content = _content }; + content = { summary = _summary; status = _status; content }; } :: rest -> - let content = block ~config ~resolve doc in - (continue_with [@tailcall]) rest content + let doc_content = block ~config ~resolve doc in + let included_content = walk_items [] content in + let all_content = doc_content @ included_content in + (continue_with [@tailcall]) rest all_content | Declaration { attr = _attr; diff --git a/test/integration/markdown.t/run.t b/test/integration/markdown.t/run.t index c270ee0fad..6a9dc6f8eb 100644 --- a/test/integration/markdown.t/run.t +++ b/test/integration/markdown.t/run.t @@ -71,6 +71,10 @@ $ cat markdown/test/Test-module-type-T.md # Module type `Test.T` + + ``` + type t = int + ``` $ cat markdown/test/Test-List.md