From 620034bc11c254f29a3a662096d58dc52c087fba Mon Sep 17 00:00:00 2001 From: Thibaut Mattio Date: Wed, 17 May 2023 13:49:45 +0200 Subject: [PATCH 01/11] Refactor comment parsing to use odoc-parser and cmarkit MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Omd 2.X doesn't support printing markdown, so OCaml LSP is blocked to Omd 1.X. This creates conflicts with codebases that have migrated to Omd 2.X (e.g. in ocamlorg). To avoid conflicts for users of Omd 2.X, we migrate to cmarkit, which has a smaller dependency profile and supports printing to markdown. Co-authored-by: Rafał Gwoździński --- dune-project | 4 +- flake.nix | 4 +- ocaml-lsp-server.opam | 4 +- ocaml-lsp-server/src/doc_to_md.ml | 408 ++++++++++++------ ocaml-lsp-server/src/dune | 4 +- .../e2e/__tests__/ocamllsp-hoverExtended.ts | 20 +- .../e2e/__tests__/textDocument-hover.test.ts | 20 +- .../__tests__/textDocument-signatureHelp.ts | 98 +++-- 8 files changed, 367 insertions(+), 195 deletions(-) diff --git a/dune-project b/dune-project index 8420d9c41..b8a87a2e4 100644 --- a/dune-project +++ b/dune-project @@ -56,11 +56,11 @@ possible and does not make any assumptions about IO. ordering dune-build-info spawn + (cmarkit (>= 0.2.0)) + (odoc-parser (>= 2.0.0)) (ppx_expect (and (>= v0.15.0) :with-test)) (ocamlformat (and :with-test (= 0.24.1))) (ocamlc-loc (and (>= 3.5.0) (< 3.7.0))) - (omd (and (>= 1.3.2) (< 2.0.0~alpha1))) - (octavius (>= 1.2.2)) (uutf (>= 1.0.2)) (pp (>= 1.1.2)) (csexp (>= 1.5)) diff --git a/flake.nix b/flake.nix index c22d616dc..a92dfbabc 100644 --- a/flake.nix +++ b/flake.nix @@ -76,8 +76,8 @@ duneVersion = "3"; buildInputs = with pkgs.ocamlPackages; [ ocamlc-loc - omd - octavius + odoc-parser + cmarkit dune-build-info re dune-rpc diff --git a/ocaml-lsp-server.opam b/ocaml-lsp-server.opam index 8ef8542f2..ecc301427 100644 --- a/ocaml-lsp-server.opam +++ b/ocaml-lsp-server.opam @@ -32,11 +32,11 @@ depends: [ "ordering" "dune-build-info" "spawn" + "cmarkit" {>= "0.2.0"} + "odoc-parser" {>= "2.0.0"} "ppx_expect" {>= "v0.15.0" & with-test} "ocamlformat" {with-test & = "0.24.1"} "ocamlc-loc" {>= "3.5.0" & < "3.7.0"} - "omd" {>= "1.3.2" & < "2.0.0~alpha1"} - "octavius" {>= "1.2.2"} "uutf" {>= "1.0.2"} "pp" {>= "1.1.2"} "csexp" {>= "1.5"} diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index 421636a34..e5061be35 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -1,150 +1,292 @@ open Import -module Oct = Octavius +open Cmarkit -let ocaml = "ocaml" +(** TODO: -let to_inline_code code = Omd.Code (ocaml, code) + - Add support for references + - Broken lists + - Labels in headers + - Align text with HTML + - Verbatim is indented in tests -let to_code_block code = Omd.Code_block (ocaml, code) + Unsupported (next): -let space = Omd.Text " " + - Support meta from odoc-parser locations *) -let new_line = Omd.NL +type t = + | Raw of string + | Markdown of string -(* [put_in_between elem lst] inserts [elem] between all elements of [lst] *) -let put_in_between elem lst = - let rec loop acc = function - | [] -> acc - | [ hd ] -> hd :: acc - | hd :: tail -> loop (elem :: hd :: acc) tail - in - List.rev (loop [] lst) - -let heading_level level heading : Omd.element = - match level with - | 0 -> H1 heading - | 1 -> H2 heading - | 2 -> H3 heading - | 3 -> H4 heading - | 4 -> H5 heading - | _ -> H6 heading - -let style_markdown (kind : Oct.Types.style_kind) md : Omd.element list = - match kind with - | SK_bold -> [ Bold md ] - | SK_italic | SK_emphasize -> [ Emph md ] - | SK_center | SK_left | SK_right | SK_superscript | SK_subscript | SK_custom _ - -> - (* TODO: implement SK_{center, left, right, superscript, subscript, custom} - using html blocks *) - md - -let rec text_to_markdown doc = List.concat_map ~f:text_element_to_markdown doc - -and text_element_to_markdown (doc_elem : Oct.Types.text_element) = - match doc_elem with - | Raw text -> [ Omd.Text text ] - | Code code -> [ to_inline_code code ] - | PreCode code -> [ to_code_block code ] - | Verbatim text -> [ Raw text ] - | Style (kind, text) -> style_markdown kind @@ text_to_markdown text - | List l -> [ Ul (text_elements_to_markdown l) ] - | Enum l -> [ Ol (text_elements_to_markdown l) ] - | Newline -> [ new_line; new_line ] - | Title (i, _, content) -> - (* TODO: along with cross-references support, add support for labels *) - let heading = text_to_markdown content in - [ heading_level i heading ] - | Ref (RK_link, url, descr) -> - let descr = - Option.map descr ~f:text_to_markdown |> Option.value ~default:[] +let loc_to_meta _loc = Meta.none + +let style_inline ~meta (style : Odoc_parser.Ast.style) inline = + match style with + | `Bold -> Inline.Strong_emphasis (Inline.Emphasis.make inline, meta) + | `Italic -> Inline.Emphasis (Inline.Emphasis.make inline, meta) + | `Emphasis -> Inline.Emphasis (Inline.Emphasis.make inline, meta) + | `Superscript -> inline + | `Subscript -> inline + +let rec inline_element_to_inline + (inline : Odoc_parser.Ast.inline_element Odoc_parser.Loc.with_location) : + Inline.t = + match inline with + | Odoc_parser.Loc.{ value = `Space _; location } -> + let meta = loc_to_meta location in + Inline.Text (" ", meta) + | Odoc_parser.Loc.{ value = `Word w; location } -> + let meta = loc_to_meta location in + Inline.Text (w, meta) + | Odoc_parser.Loc.{ value = `Code_span c; location } -> + let meta = loc_to_meta location in + Inline.Code_span (Inline.Code_span.of_string c, meta) + | Odoc_parser.Loc.{ value = `Raw_markup (Some "html", text); location } -> + let meta = loc_to_meta location in + Inline.Raw_html (Block_line.tight_list_of_string text, meta) + | Odoc_parser.Loc.{ value = `Raw_markup (_, text); location } -> + (* Cmarkit doesn't have constructors for backend other than HTML for inline + raw markups, only for blocks. *) + let meta = loc_to_meta location in + Inline.Text (text, meta) + | Odoc_parser.Loc.{ value = `Styled (style, inlines); location } -> + let text = inline_element_list_to_inlines inlines in + let meta = loc_to_meta location in + style_inline ~meta style text + | Odoc_parser.Loc. + { value = `Reference (_kind, _ref, _inlines); location = _location } -> + (* TODO: add support for references *) + Inline.Break (Inline.Break.make `Hard, Meta.none) + | Odoc_parser.Loc.{ value = `Link (link, inlines); location } -> + let text = inline_element_list_to_inlines inlines in + let ref = + `Inline (Link_definition.make ~dest:(link, Meta.none) (), Meta.none) + in + let link = Inline.Link.make text ref in + let meta = loc_to_meta location in + Inline.Link (link, meta) + | Odoc_parser.Loc.{ value = `Math_span text; location } -> + let meta = loc_to_meta location in + Inline.Ext_math_span + ( Inline.Math_span.make + ~display:false + (Block_line.tight_list_of_string text) + , meta ) + +and inline_element_list_to_inlines inlines = + let inlines = List.map ~f:inline_element_to_inline inlines in + Inline.Inlines (inlines, Meta.none) + +let rec nestable_block_element_to_block + (nestable : + Odoc_parser.Ast.nestable_block_element Odoc_parser.Loc.with_location) = + match nestable with + | Odoc_parser.Loc.{ value = `Paragraph text; location } -> + let inline = inline_element_list_to_inlines text in + let paragraph = Block.Paragraph.make inline in + let meta = loc_to_meta location in + Block.Paragraph (paragraph, meta) + | Odoc_parser.Loc.{ value = `List (kind, style, xs); location } -> + let type' = + match kind with + | `Unordered -> `Unordered '*' + | `Ordered -> `Ordered (1, '*') + in + let tight = + match style with + | `Heavy -> false + | `Light -> true + in + let list_items = + List.map + ~f:(fun n -> + let block = nestable_block_element_list_to_block n in + (Block.List_item.make block, Meta.none)) + xs + in + let l = Block.List'.make ~tight type' list_items in + let meta = loc_to_meta location in + Block.List (l, meta) + | Odoc_parser.Loc.{ value = `Modules modules; location } -> + let type' = `Unordered '*' in + let tight = false in + let list_items = + List.map + ~f:(fun Odoc_parser.Loc.{ value = m; location } -> + let inline = Inline.Text (m, Meta.none) in + let paragraph = Block.Paragraph.make inline in + let block = Block.Paragraph (paragraph, Meta.none) in + let meta = loc_to_meta location in + let marker = Layout.string "!modules:" in + (Block.List_item.make ~marker block, meta)) + modules + in + let l = Block.List'.make ~tight type' list_items in + let meta = loc_to_meta location in + Block.List (l, meta) + | Odoc_parser.Loc. + { value = `Code_block (metadata, { value = code; location = _code_loc }) + ; location + } -> + let info_string = + match metadata with + | None -> None + | Some ({ value = lang; location = lang_log }, _env) -> + Some (lang, loc_to_meta lang_log) in - let empty_title = "" in - [ Url (url, descr, empty_title) ] - | Ref (_ref_kind, reference, descr) -> - (* TODO: add support for cross-references *) - Option.map ~f:text_to_markdown descr - |> Option.value ~default:[ to_inline_code reference ] - | Special_ref _ - | Target (_, _) (* TODO: add support for markdown-specific blocks *) -> [] - -and text_elements_to_markdown lst = List.map ~f:text_to_markdown lst - -let rec tags_to_markdown (tags : Oct.Types.tag list) = - List.map ~f:tag_to_markdown tags - |> put_in_between [ new_line; new_line ] - |> List.concat - -and tag_to_markdown tag : Omd.element list = - let format_tag tag = Omd.Bold [ Emph [ Text tag ] ] in - let plain_tag_to_md tag descr = [ format_tag tag; space; Text descr ] in - let tag_with_text_to_md tag text = - format_tag tag :: space :: text_to_markdown text + let block_line = Block_line.list_of_string code in + let code_block = Block.Code_block.make ?info_string block_line in + let meta = loc_to_meta location in + Block.Code_block (code_block, meta) + | Odoc_parser.Loc.{ value = `Verbatim code; location } -> + let info_string = Some ("verb", Meta.none) in + let block_line = Block_line.list_of_string code in + let code_block = Block.Code_block.make ?info_string block_line in + let meta = loc_to_meta location in + Block.Code_block (code_block, meta) + | Odoc_parser.Loc.{ value = `Math_block code; location } -> + let block_line = Block_line.list_of_string code in + let code_block = Block.Code_block.make block_line in + let meta = loc_to_meta location in + Block.Ext_math_block (code_block, meta) + +and nestable_block_element_list_to_block nestables = + let blocks = List.map ~f:nestable_block_element_to_block nestables in + Block.Blocks (blocks, Meta.none) + +let strong_and_emphasis s = + Inline.Emphasis + ( Inline.Emphasis.make + (Inline.Strong_emphasis + (Inline.Emphasis.make (Inline.Text (s, Meta.none)), Meta.none)) + , Meta.none ) + +let inline_code_span_of_string s = + Inline.Code_span + ( Inline.Code_span.make ~backtick_count:1 (Block_line.tight_list_of_string s) + , Meta.none ) + +let inline_link_of_string ~text uri = + let ref = + `Inline (Link_definition.make ~dest:(uri, Meta.none) (), Meta.none) in - let marked_tag_to_md tag mark = - [ format_tag tag; space; to_inline_code mark ] + Inline.Link (Inline.Link.make (Inline.Text (text, Meta.none)) ref, Meta.none) + +let tag_to_block ~meta (tag : Odoc_parser.Ast.tag) = + let format_tag_empty tag = + Block.Paragraph (Block.Paragraph.make (strong_and_emphasis tag), Meta.none) in - let marked_tag_with_text_to_md tag mark text = - format_tag tag :: space :: to_inline_code mark :: space - :: text_to_markdown text + let format_tag_string tag text = + let inline = + Inline.Inlines + ( [ strong_and_emphasis tag; Inline.Text (" ", Meta.none); text ] + , Meta.none ) + in + Block.Paragraph (Block.Paragraph.make inline, meta) in - let see_tag_to_md (see_ref, comment) = - let content = - match (see_ref, comment) with - | Oct.Types.See_url url, text -> - let empty_hover_title = "" in - let link_title = [ Omd.Text "link" ] in - Omd.Url (url, link_title, empty_hover_title) - :: space :: text_to_markdown text - | See_file name, text | See_doc name, text -> - let no_prog_lang = "" in - (* TODO: add support to reference files and documents *) - Code (no_prog_lang, name) :: space :: text_to_markdown text + let format_tag_block tag block = + let prefix = + Block.Paragraph (Block.Paragraph.make (strong_and_emphasis tag), Meta.none) in - format_tag "@see" :: space :: content + Block.Blocks ([ prefix; block ], meta) + in + let format_tag_string_with_block tag text block = + let prefix = + let inline = + Inline.Inlines + ( [ strong_and_emphasis tag; Inline.Text (" ", Meta.none); text ] + , Meta.none ) + in + Block.Paragraph (Block.Paragraph.make inline, Meta.none) + in + Block.Blocks ([ prefix; block ], meta) in match tag with - | Author a -> plain_tag_to_md "@author" a - | Canonical c -> plain_tag_to_md "@canonical" c - | Deprecated text -> tag_with_text_to_md "@deprecated" text - | Return_value text -> tag_with_text_to_md "@return" text - | Version v -> marked_tag_to_md "@version" v - | Since v -> marked_tag_to_md "@since" v - | Before (ver, text) -> ( - match text with - | [] -> marked_tag_to_md "@before" ver - | _ -> marked_tag_with_text_to_md "@before" ver text) - | Param (name, text) -> ( - match text with - | [] -> - tag_with_text_to_md "@param" [ Raw name ] (* in case `id` is missing) *) - | _ -> marked_tag_with_text_to_md "@param" name text) - | Raised_exception (exn, text) -> marked_tag_with_text_to_md "@raise" exn text - | See (r, s) -> see_tag_to_md (r, s) - | Custom (name, text) -> - [ Omd.Emph [ Text ("@" ^ name) ]; space ] @ text_to_markdown text - | Inline -> [ Emph [ Text "@inline" ] ] - -let comment_to_markdown (doc, tags) = - let text = text_to_markdown doc in - let tags = tags_to_markdown tags in - match tags with - | [] -> text - | non_empty_tags -> - let separation = Omd.[ NL; Hr ] in - text @ separation @ non_empty_tags + | `Author s -> + let s = Inline.Text (s, Meta.none) in + format_tag_string "@author" s + | `Deprecated text -> + let block = nestable_block_element_list_to_block text in + format_tag_block "@deprecated" block + | `Param (id, []) -> + let id = Inline.Text (id, Meta.none) in + format_tag_string "@param" id + | `Param (id, text) -> + let block = nestable_block_element_list_to_block text in + let id = inline_code_span_of_string id in + format_tag_string_with_block "@param" id block + | `Raise (exc, text) -> + let block = nestable_block_element_list_to_block text in + let exc = inline_code_span_of_string exc in + format_tag_string_with_block "@raise" exc block + | `Return text -> + let block = nestable_block_element_list_to_block text in + format_tag_block "@return" block + | `See (`Url, uri, text) -> + let block = nestable_block_element_list_to_block text in + let uri = inline_link_of_string ~text:"link" uri in + format_tag_string_with_block "@see" uri block + | `See ((`File | `Document), uri, text) -> + let block = nestable_block_element_list_to_block text in + let uri = inline_code_span_of_string uri in + format_tag_string_with_block "@see" uri block + | `Since version -> + let version = inline_code_span_of_string version in + format_tag_string "@since" version + | `Before (version, text) -> + let block = nestable_block_element_list_to_block text in + let version = inline_code_span_of_string version in + format_tag_string_with_block "@before" version block + | `Version version -> + let version = inline_code_span_of_string version in + format_tag_string "@version" version + | `Canonical { value = s; location = _ } -> + let s = Inline.Text (s, Meta.none) in + format_tag_string "@canonical" s + | `Inline -> format_tag_empty "@inline" + | `Open -> format_tag_empty "@open" + | `Closed -> format_tag_empty "@closed" -type t = - | Raw of string - | Markdown of string +let rec block_element_to_block + (block_element : + Odoc_parser.Ast.block_element Odoc_parser.Loc.with_location) = + match block_element with + | Odoc_parser.Loc.{ value = `Heading (level, _, content); location } -> + let text = inline_element_list_to_inlines content in + let heading = Block.Heading.make ~level text in + let meta = loc_to_meta location in + Block.Heading (heading, meta) + | Odoc_parser.Loc.{ value = `Tag t; location } -> + let meta = loc_to_meta location in + tag_to_block ~meta t + | Odoc_parser.Loc. + { value = + ( `Paragraph _ + | `List _ + | `Modules _ + | `Code_block _ + | `Verbatim _ + | `Math_block _ ) + ; location = _ + } as nestable -> nestable_block_element_to_block nestable + +and block_element_list_to_block l = + let rec aux acc rest = + match rest with + | [] -> List.rev acc + | el :: [] -> List.rev (block_element_to_block el :: acc) + | el :: rest -> + aux + (Block.Blank_line ("", Meta.none) :: block_element_to_block el :: acc) + rest + in + let blocks = aux [] l in + Block.Blocks (blocks, Meta.none) let translate doc : t = - match Oct.parse (Lexing.from_string doc) with - | Error e -> - let msg = Oct.Errors.message e.error in - Log.log ~section:"debug" (fun () -> - Log.msg "invalid doc comments" [ ("msg", `String msg) ]); - Raw (Omd.to_markdown [ Raw doc ]) - | Ok doc -> - let doc = comment_to_markdown doc in - Markdown (Omd.to_markdown doc) + let location = Lexing.dummy_pos in + let v = Odoc_parser.parse_comment ~location ~text:doc in + let ast = Odoc_parser.ast v in + let block = block_element_list_to_block ast in + let doc = Doc.make block in + let cmark = Cmarkit_commonmark.of_doc doc in + Markdown cmark diff --git a/ocaml-lsp-server/src/dune b/ocaml-lsp-server/src/dune index 6f0584538..c62a1507e 100644 --- a/ocaml-lsp-server/src/dune +++ b/ocaml-lsp-server/src/dune @@ -24,8 +24,8 @@ merlin-lib.ocaml_utils merlin-lib.utils merlin-lib.extend - octavius - omd + cmarkit + odoc-parser ppx_yojson_conv_lib re stdune diff --git a/ocaml-lsp-server/test/e2e/__tests__/ocamllsp-hoverExtended.ts b/ocaml-lsp-server/test/e2e/__tests__/ocamllsp-hoverExtended.ts index 142c58364..52241e90f 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/ocamllsp-hoverExtended.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/ocamllsp-hoverExtended.ts @@ -219,24 +219,30 @@ describe("ocamllsp/hoverExtended", () => { This function has a nice documentation. It performs division of two integer numbers. - * * * - ***@param*** \`x\` dividend + + ***@param*** \`x\` + dividend ***@param*** divisor - ***@return*** *quotient*, i.e. result of division + ***@return*** + *quotient*, i.e. result of division - ***@raise*** \`Division_by_zero\` raised when divided by zero + ***@raise*** \`Division_by_zero\` + raised when divided by zero - ***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_(%C3%B7,_or_/)) article + ***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_\\(%C3%B7,_or_/\\)) + article - ***@see*** \`arithmetic.ml\` for more context + ***@see*** \`arithmetic.ml\` + for more context ***@since*** \`4.0.0\` ***@before*** \`4.4.0\` - ***@deprecated*** use \`(/)\` + ***@deprecated*** + use \`(/)\` ***@version*** \`1.0.0\` diff --git a/ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts b/ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts index b2534b49a..0484b048d 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts @@ -258,24 +258,30 @@ describe("textDocument/hover", () => { This function has a nice documentation. It performs division of two integer numbers. - * * * - ***@param*** \`x\` dividend + + ***@param*** \`x\` + dividend ***@param*** divisor - ***@return*** *quotient*, i.e. result of division + ***@return*** + *quotient*, i.e. result of division - ***@raise*** \`Division_by_zero\` raised when divided by zero + ***@raise*** \`Division_by_zero\` + raised when divided by zero - ***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_(%C3%B7,_or_/)) article + ***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_\\(%C3%B7,_or_/\\)) + article - ***@see*** \`arithmetic.ml\` for more context + ***@see*** \`arithmetic.ml\` + for more context ***@since*** \`4.0.0\` ***@before*** \`4.4.0\` - ***@deprecated*** use \`(/)\` + ***@deprecated*** + use \`(/)\` ***@version*** \`1.0.0\` diff --git a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts index c6d0f7bd5..3c4fca998 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts @@ -296,7 +296,7 @@ describe_opt("textDocument/completion", () => { {3 Module List} {!modules: Array List String} - + @param x dividend @param divisor @@ -338,72 +338,90 @@ describe_opt("textDocument/completion", () => { documentation: { kind: "markdown", value: outdent`This is an example of a docstring that demonstrates various ocamldoc syntax features. - - #### Sections and Labels - We can create sections using #### Section title - and labels using #### Section title with label + ### Sections and Labels + + We can create sections using + + ### Section title - #### Links and Cross-references + and labels using + + ### Section title with label + + ### Links and Cross-references External links: [OCaml's official website](https://ocaml.org/) - #### Inline Formatting + ### Inline Formatting **Bold**, *Italic*, *Emphasize*, Superscript, Subscript, and \`inline code\` - #### Text Alignment - + ### Text Alignment + Centered text - Left-aligned text - Right-aligned text - #### Lists + Left-aligned text - 1. Ordered list item 1 - 2. Ordered list item 2 + Right-aligned text - - Unordered list item 1 - - Unordered list item 2 + ### Lists - - Unordered list item 1 - - Unordered list item 2 + 1.Ordered list item 1 + 2.Ordered list item 2 + + *Unordered list item 1 + *Unordered list item 2 + + *Unordered list item 1 + *Unordered list item 2 - #### Code Blocks + ### Code Blocks - \`\`\`ocaml - let square x = x * x - let result = square 3 + \`\`\` + let square x = x * x + let result = square 3 \`\`\` - #### Verbatim + ### Verbatim + \`\`\`verb This text will be displayed verbatim. No formatting will be applied. + \`\`\` - #### Module List + ### Module List - * * * - ***@param*** \`x\` dividend + *Array + *List + *String + ***@param*** \`x\` + dividend + ***@param*** divisor - - ***@return*** *quotient*, i.e. result of division - - ***@raise*** \`Division_by_zero\` raised when divided by zero - - ***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_(%C3%B7,_or_/)) article - - ***@see*** \`arithmetic.ml\` for more context - + + ***@return*** + *quotient*, i.e. result of division + + ***@raise*** \`Division_by_zero\` + raised when divided by zero + + ***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_\\(%C3%B7,_or_/\\)) + article + + ***@see*** \`arithmetic.ml\` + for more context + ***@since*** \`4.0.0\` - + ***@before*** \`4.4.0\` - - ***@deprecated*** use \`(/)\` - + + ***@deprecated*** + use \`(/)\` + ***@version*** \`1.0.0\` - + ***@author*** John Doe `, }, From d4824da22ccde618c32f6d7846f1e8f2f812cc01 Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Wed, 17 May 2023 15:12:56 +0200 Subject: [PATCH 02/11] Fix comment parsing tests --- ocaml-lsp-server/src/doc_to_md.ml | 8 ++--- .../__tests__/textDocument-signatureHelp.ts | 30 +++++++++---------- 2 files changed, 19 insertions(+), 19 deletions(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index e5061be35..425e3a158 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -88,7 +88,7 @@ let rec nestable_block_element_to_block | Odoc_parser.Loc.{ value = `List (kind, style, xs); location } -> let type' = match kind with - | `Unordered -> `Unordered '*' + | `Unordered -> `Unordered '-' | `Ordered -> `Ordered (1, '*') in let tight = @@ -124,12 +124,12 @@ let rec nestable_block_element_to_block let meta = loc_to_meta location in Block.List (l, meta) | Odoc_parser.Loc. - { value = `Code_block (metadata, { value = code; location = _code_loc }) + { value = `Code_block (metadata, { value = code; location = code_loc }) ; location } -> let info_string = match metadata with - | None -> None + | None -> Some ("ocaml", loc_to_meta code_loc) | Some ({ value = lang; location = lang_log }, _env) -> Some (lang, loc_to_meta lang_log) in @@ -252,7 +252,7 @@ let rec block_element_to_block match block_element with | Odoc_parser.Loc.{ value = `Heading (level, _, content); location } -> let text = inline_element_list_to_inlines content in - let heading = Block.Heading.make ~level text in + let heading = Block.Heading.make ~level:(level+1) text in let meta = loc_to_meta location in Block.Heading (heading, meta) | Odoc_parser.Loc.{ value = `Tag t; location } -> diff --git a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts index 3c4fca998..fec583d0a 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts @@ -339,25 +339,25 @@ describe_opt("textDocument/completion", () => { kind: "markdown", value: outdent`This is an example of a docstring that demonstrates various ocamldoc syntax features. - ### Sections and Labels + #### Sections and Labels We can create sections using - ### Section title + #### Section title and labels using - ### Section title with label + #### Section title with label - ### Links and Cross-references + #### Links and Cross-references External links: [OCaml's official website](https://ocaml.org/) - ### Inline Formatting + #### Inline Formatting **Bold**, *Italic*, *Emphasize*, Superscript, Subscript, and \`inline code\` - ### Text Alignment + #### Text Alignment Centered text @@ -365,32 +365,32 @@ describe_opt("textDocument/completion", () => { Right-aligned text - ### Lists + #### Lists 1.Ordered list item 1 2.Ordered list item 2 - *Unordered list item 1 - *Unordered list item 2 + -Unordered list item 1 + -Unordered list item 2 - *Unordered list item 1 - *Unordered list item 2 + -Unordered list item 1 + -Unordered list item 2 - ### Code Blocks + #### Code Blocks - \`\`\` + \`\`\`ocaml let square x = x * x let result = square 3 \`\`\` - ### Verbatim + #### Verbatim \`\`\`verb This text will be displayed verbatim. No formatting will be applied. \`\`\` - ### Module List + #### Module List *Array *List From c9431bc27e9453a0c722b9a0c2d4babe36df8ef9 Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Wed, 17 May 2023 17:13:34 +0200 Subject: [PATCH 03/11] Add test for code block language header --- .../test/e2e/__tests__/textDocument-signatureHelp.ts | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts index fec583d0a..5d505f2bc 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts @@ -285,6 +285,11 @@ describe_opt("textDocument/completion", () => { let square x = x * x let result = square 3 ]} + + {@python[ + def f(): + return 0 + ]} {3 Verbatim} @@ -382,7 +387,12 @@ describe_opt("textDocument/completion", () => { let square x = x * x let result = square 3 \`\`\` - + + \`\`\`python + def f(): + return 0 + \`\`\` + #### Verbatim \`\`\`verb From a2f91fc584d9ef0863548d975d3318cbf02e7eb7 Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Wed, 17 May 2023 17:15:18 +0200 Subject: [PATCH 04/11] fmt --- ocaml-lsp-server/src/doc_to_md.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index 425e3a158..b1037e9a7 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -252,7 +252,7 @@ let rec block_element_to_block match block_element with | Odoc_parser.Loc.{ value = `Heading (level, _, content); location } -> let text = inline_element_list_to_inlines content in - let heading = Block.Heading.make ~level:(level+1) text in + let heading = Block.Heading.make ~level:(level + 1) text in let meta = loc_to_meta location in Block.Heading (heading, meta) | Odoc_parser.Loc.{ value = `Tag t; location } -> From 91a1598cd8aee966ded6b0356797c19e158ba863 Mon Sep 17 00:00:00 2001 From: Thibaut Mattio Date: Wed, 17 May 2023 19:00:24 +0200 Subject: [PATCH 05/11] Add a changelog entry --- CHANGES.md | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/CHANGES.md b/CHANGES.md index 479cfcaf6..9916e6c87 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -2,6 +2,15 @@ ## Fixes +- Refactor comment parsing to use `odoc-parser` and `cmarkit` instead of + `octavius` and `omd` (#1088) + + This allows users who migrated to omd 2.X to install ocaml-lsp-server in the + same opam switch. + + We also slightly improved markdown generation support and fixed a couple in + the generation of inline heading and module types. + - Allow opening documents that were already open. This is a workaround for neovim's lsp client (#1067) From 832590253be3aa2b5e3cb3561b1ed2a679b6a287 Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Thu, 18 May 2023 10:04:37 +0200 Subject: [PATCH 06/11] Fix list indentation --- ocaml-lsp-server/src/doc_to_md.ml | 2 +- .../test/e2e/__tests__/textDocument-signatureHelp.ts | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index b1037e9a7..a1fb8b927 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -100,7 +100,7 @@ let rec nestable_block_element_to_block List.map ~f:(fun n -> let block = nestable_block_element_list_to_block n in - (Block.List_item.make block, Meta.none)) + (Block.List_item.make ~after_marker:1 block, Meta.none)) xs in let l = Block.List'.make ~tight type' list_items in diff --git a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts index 5d505f2bc..7fef18d32 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts @@ -372,14 +372,14 @@ describe_opt("textDocument/completion", () => { #### Lists - 1.Ordered list item 1 - 2.Ordered list item 2 + 1. Ordered list item 1 + 2. Ordered list item 2 - -Unordered list item 1 - -Unordered list item 2 + - Unordered list item 1 + - Unordered list item 2 - -Unordered list item 1 - -Unordered list item 2 + - Unordered list item 1 + - Unordered list item 2 #### Code Blocks From 303d6f315920da077fd42616a20d0c0e2aa6d2ee Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Thu, 18 May 2023 10:29:21 +0200 Subject: [PATCH 07/11] Update doc_to_md TODO --- ocaml-lsp-server/src/doc_to_md.ml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index a1fb8b927..9f54f3a08 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -4,7 +4,7 @@ open Cmarkit (** TODO: - Add support for references - - Broken lists + - Broken module lists - Labels in headers - Align text with HTML - Verbatim is indented in tests From 6b0765173b89863abf4861b2ee1ce08415453d40 Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Thu, 18 May 2023 10:38:56 +0200 Subject: [PATCH 08/11] Update opam-repository in flake.lock --- flake.lock | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/flake.lock b/flake.lock index e12797907..3f8762109 100644 --- a/flake.lock +++ b/flake.lock @@ -142,11 +142,11 @@ "opam-repository": { "flake": false, "locked": { - "lastModified": 1682021363, - "narHash": "sha256-nDUDFwyOTZDALeqqEDnF2PTPIHT4sVYdQXUbRt03oNs=", + "lastModified": 1684354567, + "narHash": "sha256-e6Ohs0riGaIUtUt1vI29rNmeJxHJFe/cgG7IUmIcYNs=", "owner": "ocaml", "repo": "opam-repository", - "rev": "786c55fa77c37f07eceea7d6a9bec04d2225e302", + "rev": "8e3f9bbe3f849d3eff023b1cdb0d66069c93435c", "type": "github" }, "original": { From f059af2b2eba89fea4e2901a0318ebe8cf16cdbe Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Fri, 19 May 2023 07:21:15 +0200 Subject: [PATCH 09/11] Fix module lists --- ocaml-lsp-server/src/doc_to_md.ml | 2 +- .../test/e2e/__tests__/textDocument-signatureHelp.ts | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index 9f54f3a08..6600225f1 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -117,7 +117,7 @@ let rec nestable_block_element_to_block let block = Block.Paragraph (paragraph, Meta.none) in let meta = loc_to_meta location in let marker = Layout.string "!modules:" in - (Block.List_item.make ~marker block, meta)) + (Block.List_item.make ~after_marker:1 ~marker block, meta)) modules in let l = Block.List'.make ~tight type' list_items in diff --git a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts index 7fef18d32..80c598a69 100644 --- a/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts +++ b/ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts @@ -402,9 +402,9 @@ describe_opt("textDocument/completion", () => { #### Module List - *Array - *List - *String + * Array + * List + * String ***@param*** \`x\` dividend From d0fea98570bcd158ad8ebffcaadbbb6cc3c5cd37 Mon Sep 17 00:00:00 2001 From: Rafal Gwozdzinski Date: Fri, 19 May 2023 07:22:14 +0200 Subject: [PATCH 10/11] Update TODO --- ocaml-lsp-server/src/doc_to_md.ml | 1 - 1 file changed, 1 deletion(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index 6600225f1..793085a07 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -4,7 +4,6 @@ open Cmarkit (** TODO: - Add support for references - - Broken module lists - Labels in headers - Align text with HTML - Verbatim is indented in tests From 8406a9e9e56a0759e41ad1d4198a172129e29978 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Thu, 8 Jun 2023 16:03:48 +0100 Subject: [PATCH 11/11] _ Signed-off-by: Rudi Grinberg --- ocaml-lsp-server/src/doc_to_md.ml | 77 ++++++++++++++++--------------- 1 file changed, 40 insertions(+), 37 deletions(-) diff --git a/ocaml-lsp-server/src/doc_to_md.ml b/ocaml-lsp-server/src/doc_to_md.ml index 793085a07..a2a80a5d6 100644 --- a/ocaml-lsp-server/src/doc_to_md.ml +++ b/ocaml-lsp-server/src/doc_to_md.ml @@ -1,5 +1,15 @@ open Import -open Cmarkit + +open struct + open Cmarkit + module Inline = Inline + module Meta = Meta + module Block_line = Block_line + module Link_definition = Link_definition + module Block = Block + module Layout = Layout + module Doc = Doc +end (** TODO: @@ -30,32 +40,31 @@ let rec inline_element_to_inline (inline : Odoc_parser.Ast.inline_element Odoc_parser.Loc.with_location) : Inline.t = match inline with - | Odoc_parser.Loc.{ value = `Space _; location } -> + | { value = `Space _; location } -> let meta = loc_to_meta location in Inline.Text (" ", meta) - | Odoc_parser.Loc.{ value = `Word w; location } -> + | { value = `Word w; location } -> let meta = loc_to_meta location in Inline.Text (w, meta) - | Odoc_parser.Loc.{ value = `Code_span c; location } -> + | { value = `Code_span c; location } -> let meta = loc_to_meta location in Inline.Code_span (Inline.Code_span.of_string c, meta) | Odoc_parser.Loc.{ value = `Raw_markup (Some "html", text); location } -> let meta = loc_to_meta location in Inline.Raw_html (Block_line.tight_list_of_string text, meta) - | Odoc_parser.Loc.{ value = `Raw_markup (_, text); location } -> + | { value = `Raw_markup (_, text); location } -> (* Cmarkit doesn't have constructors for backend other than HTML for inline raw markups, only for blocks. *) let meta = loc_to_meta location in Inline.Text (text, meta) - | Odoc_parser.Loc.{ value = `Styled (style, inlines); location } -> + | { value = `Styled (style, inlines); location } -> let text = inline_element_list_to_inlines inlines in let meta = loc_to_meta location in style_inline ~meta style text - | Odoc_parser.Loc. - { value = `Reference (_kind, _ref, _inlines); location = _location } -> + | { value = `Reference (_kind, _ref, _inlines); location = _location } -> (* TODO: add support for references *) Inline.Break (Inline.Break.make `Hard, Meta.none) - | Odoc_parser.Loc.{ value = `Link (link, inlines); location } -> + | { value = `Link (link, inlines); location } -> let text = inline_element_list_to_inlines inlines in let ref = `Inline (Link_definition.make ~dest:(link, Meta.none) (), Meta.none) @@ -63,7 +72,7 @@ let rec inline_element_to_inline let link = Inline.Link.make text ref in let meta = loc_to_meta location in Inline.Link (link, meta) - | Odoc_parser.Loc.{ value = `Math_span text; location } -> + | { value = `Math_span text; location } -> let meta = loc_to_meta location in Inline.Ext_math_span ( Inline.Math_span.make @@ -79,12 +88,12 @@ let rec nestable_block_element_to_block (nestable : Odoc_parser.Ast.nestable_block_element Odoc_parser.Loc.with_location) = match nestable with - | Odoc_parser.Loc.{ value = `Paragraph text; location } -> + | { value = `Paragraph text; location } -> let inline = inline_element_list_to_inlines text in let paragraph = Block.Paragraph.make inline in let meta = loc_to_meta location in Block.Paragraph (paragraph, meta) - | Odoc_parser.Loc.{ value = `List (kind, style, xs); location } -> + | { value = `List (kind, style, xs); location } -> let type' = match kind with | `Unordered -> `Unordered '-' @@ -96,36 +105,31 @@ let rec nestable_block_element_to_block | `Light -> true in let list_items = - List.map - ~f:(fun n -> + List.map xs ~f:(fun n -> let block = nestable_block_element_list_to_block n in (Block.List_item.make ~after_marker:1 block, Meta.none)) - xs in let l = Block.List'.make ~tight type' list_items in let meta = loc_to_meta location in Block.List (l, meta) - | Odoc_parser.Loc.{ value = `Modules modules; location } -> + | { value = `Modules modules; location } -> let type' = `Unordered '*' in let tight = false in let list_items = - List.map - ~f:(fun Odoc_parser.Loc.{ value = m; location } -> + List.map modules ~f:(fun Odoc_parser.Loc.{ value = m; location } -> let inline = Inline.Text (m, Meta.none) in let paragraph = Block.Paragraph.make inline in let block = Block.Paragraph (paragraph, Meta.none) in let meta = loc_to_meta location in let marker = Layout.string "!modules:" in (Block.List_item.make ~after_marker:1 ~marker block, meta)) - modules in let l = Block.List'.make ~tight type' list_items in let meta = loc_to_meta location in Block.List (l, meta) - | Odoc_parser.Loc. - { value = `Code_block (metadata, { value = code; location = code_loc }) - ; location - } -> + | { value = `Code_block (metadata, { value = code; location = code_loc }) + ; location + } -> let info_string = match metadata with | None -> Some ("ocaml", loc_to_meta code_loc) @@ -136,13 +140,13 @@ let rec nestable_block_element_to_block let code_block = Block.Code_block.make ?info_string block_line in let meta = loc_to_meta location in Block.Code_block (code_block, meta) - | Odoc_parser.Loc.{ value = `Verbatim code; location } -> + | { value = `Verbatim code; location } -> let info_string = Some ("verb", Meta.none) in let block_line = Block_line.list_of_string code in let code_block = Block.Code_block.make ?info_string block_line in let meta = loc_to_meta location in Block.Code_block (code_block, meta) - | Odoc_parser.Loc.{ value = `Math_block code; location } -> + | { value = `Math_block code; location } -> let block_line = Block_line.list_of_string code in let code_block = Block.Code_block.make block_line in let meta = loc_to_meta location in @@ -249,24 +253,23 @@ let rec block_element_to_block (block_element : Odoc_parser.Ast.block_element Odoc_parser.Loc.with_location) = match block_element with - | Odoc_parser.Loc.{ value = `Heading (level, _, content); location } -> + | { value = `Heading (level, _, content); location } -> let text = inline_element_list_to_inlines content in let heading = Block.Heading.make ~level:(level + 1) text in let meta = loc_to_meta location in Block.Heading (heading, meta) - | Odoc_parser.Loc.{ value = `Tag t; location } -> + | { value = `Tag t; location } -> let meta = loc_to_meta location in tag_to_block ~meta t - | Odoc_parser.Loc. - { value = - ( `Paragraph _ - | `List _ - | `Modules _ - | `Code_block _ - | `Verbatim _ - | `Math_block _ ) - ; location = _ - } as nestable -> nestable_block_element_to_block nestable + | { value = + ( `Paragraph _ + | `List _ + | `Modules _ + | `Code_block _ + | `Verbatim _ + | `Math_block _ ) + ; location = _ + } as nestable -> nestable_block_element_to_block nestable and block_element_list_to_block l = let rec aux acc rest =