Skip to content

Commit

Permalink
Merge dc4f566 into 6f78852
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Oct 19, 2023
2 parents 6f78852 + dc4f566 commit 7ea8e53
Show file tree
Hide file tree
Showing 24 changed files with 3,408 additions and 8 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@

## Features

- Compatibility with Odoc 2.3.0, with support for the introduced syntax: tables,
and "codeblock output" (#1184)
- Display text of references in doc strings (#1166)

- Add mark/remove unused actions for open, types, for loop indexes, modules,
Expand Down
3 changes: 2 additions & 1 deletion dune-project
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,8 @@ possible and does not make any assumptions about IO.
ordering
dune-build-info
spawn
(odoc-parser (and (>= 2.0.0) (< 2.3.0)))
astring
camlp-streams
(ppx_expect (and (>= v0.15.0) :with-test))
(ocamlformat (and :with-test (= 0.24.1)))
(ocamlc-loc (>= 3.7.0))
Expand Down
6 changes: 4 additions & 2 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,8 @@
ppx_yojson_conv_lib
uutf
lsp
odoc-parser
astring
camlp-streams
merlin-lib
];
doCheck = false;
Expand All @@ -110,7 +111,8 @@
duneVersion = "3";
buildInputs = with pkgs.ocamlPackages; [
ocamlc-loc
odoc-parser
astring
camlp-streams
dune-build-info
re
dune-rpc
Expand Down
3 changes: 2 additions & 1 deletion ocaml-lsp-server.opam
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,8 @@ depends: [
"ordering"
"dune-build-info"
"spawn"
"odoc-parser" {>= "2.0.0" & < "2.3.0"}
"astring"
"camlp-streams"
"ppx_expect" {>= "v0.15.0" & with-test}
"ocamlformat" {with-test & = "0.24.1"}
"ocamlc-loc" {>= "3.7.0"}
Expand Down
117 changes: 114 additions & 3 deletions ocaml-lsp-server/src/doc_to_md.ml
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,41 @@ let rec nestable_block_element_to_block
let paragraph = Block.Paragraph.make inline in
let meta = loc_to_meta location in
Block.Paragraph (paragraph, meta)
| { value = `Table ((grid, alignment), _); location } ->
let meta = loc_to_meta location in
let cell
((c, _) : Odoc_parser.Ast.nestable_block_element Odoc_parser.Ast.cell) =
let c = nestable_block_element_list_to_inlines c in
(c, (" ", " ") (* Initial and trailing blanks *))
in
let header_row
(row : Odoc_parser.Ast.nestable_block_element Odoc_parser.Ast.row) =
let row = List.map ~f:cell row in
((`Header row, Meta.none), "")
in
let data_row
(row : Odoc_parser.Ast.nestable_block_element Odoc_parser.Ast.row) =
let row = List.map ~f:cell row in
((`Data row, Meta.none), "")
in
let alignment_row =
match alignment with
| None -> []
| Some alignment ->
let alignment =
List.map
~f:(fun x -> ((x, 1 (* nb of separator *)), Meta.none))
alignment
in
[ ((`Sep alignment, Meta.none), "") ]
in
let rows =
match grid with
| [] -> assert false
| h :: t -> (header_row h :: alignment_row) @ List.map ~f:data_row t
in
let tbl = Block.Table.make rows in
Block.Ext_table (tbl, meta)
| { value = `List (kind, style, xs); location } ->
let type' =
match kind with
Expand Down Expand Up @@ -140,19 +175,31 @@ let rec nestable_block_element_to_block
let l = Block.List'.make ~tight type' list_items in
let meta = loc_to_meta location in
Block.List (l, meta)
| { value = `Code_block (metadata, { value = code; location = code_loc })
| { value =
`Code_block
{ meta = metadata
; delimiter = _
; content = { value = code; location = code_loc }
; output
}
; location
} ->
let info_string =
match metadata with
| None -> Some ("ocaml", loc_to_meta code_loc)
| Some ({ value = lang; location = lang_log }, _env) ->
| Some { language = { value = lang; location = lang_log }; tags = _ } ->
Some (lang, loc_to_meta lang_log)
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)
let main_block = Block.Code_block (code_block, meta) in
let output_block =
match output with
| None -> []
| Some output -> [ nestable_block_element_list_to_block output ]
in
Block.Blocks (main_block :: output_block, meta)
| { value = `Verbatim code; location } ->
let info_string = Some ("verb", Meta.none) in
let block_line = Block_line.list_of_string code in
Expand All @@ -165,6 +212,68 @@ let rec nestable_block_element_to_block
let meta = loc_to_meta location in
Block.Ext_math_block (code_block, meta)

and nestable_block_element_to_inlines
(nestable :
Odoc_parser.Ast.nestable_block_element Odoc_parser.Loc.with_location) =
match nestable with
| { value = `Paragraph text; location = _ } ->
inline_element_list_to_inlines text
| { value = `Table ((grid, _), _); location } ->
let meta = loc_to_meta location in
let cell
((c, _) : Odoc_parser.Ast.nestable_block_element Odoc_parser.Ast.cell) =
nestable_block_element_list_to_inlines c
in
let row (row : Odoc_parser.Ast.nestable_block_element Odoc_parser.Ast.row) =
let sep = Inline.Text (" | ", Meta.none) in
sep :: List.concat_map ~f:(fun c -> [ cell c; sep ]) row
in
let rows = List.concat_map ~f:row grid in
Inline.Inlines (rows, meta)
| { value = `List (_, _, xs); location } ->
let meta = loc_to_meta location in
let item i = nestable_block_element_list_to_inlines i in
let items =
let sep = Inline.Text (" - ", Meta.none) in
List.concat_map ~f:(fun i -> [ sep; item i ]) xs
in
Inline.Inlines (items, meta)
| { value = `Modules modules; location } ->
let meta = loc_to_meta location in
let s = List.map ~f:(fun x -> x.Odoc_parser.Loc.value) modules in
Inline.Text ("modules: " ^ String.concat ~sep:" " s, meta)
| { value =
`Code_block
{ meta = _
; delimiter = _
; content = { value = code; location = code_loc }
; output = _
}
; location
} ->
let meta = loc_to_meta location in
let meta_code = loc_to_meta code_loc in
let code_span =
Inline.Code_span.make ~backtick_count:1 [ ("", (code, meta_code)) ]
in
Inline.Code_span (code_span, meta)
| { value = `Verbatim code; location } ->
let meta = loc_to_meta location in
let code_span =
Inline.Code_span.make ~backtick_count:1 [ ("", (code, Meta.none)) ]
in
Inline.Code_span (code_span, meta)
| { value = `Math_block code; location } ->
let meta = loc_to_meta location in
let code_span =
Inline.Math_span.make ~display:true [ ("", (code, Meta.none)) ]
in
Inline.Ext_math_span (code_span, meta)

and nestable_block_element_list_to_inlines l =
let inlines = List.map ~f:nestable_block_element_to_inlines l in
Inline.Inlines (inlines, Meta.none)

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)
Expand Down Expand Up @@ -261,6 +370,7 @@ let tag_to_block ~meta (tag : Odoc_parser.Ast.tag) =
| `Inline -> format_tag_empty "@inline"
| `Open -> format_tag_empty "@open"
| `Closed -> format_tag_empty "@closed"
| `Hidden -> format_tag_empty "@hidden"

let rec block_element_to_block
(block_element :
Expand All @@ -280,6 +390,7 @@ let rec block_element_to_block
| `Modules _
| `Code_block _
| `Verbatim _
| `Table _
| `Math_block _ )
; location = _
} as nestable -> nestable_block_element_to_block nestable
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/dune
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
merlin-lib.utils
merlin-lib.extend
cmarkit
odoc-parser
odoc_parser
ppx_yojson_conv_lib
re
stdune
Expand Down
41 changes: 41 additions & 0 deletions ocaml-lsp-server/test/e2e-new/doc_to_md.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,3 +15,44 @@ let%expect_test "subscript" =

translate doc |> print_doc;
[%expect {| a\_{b} |}]

let%expect_test "table" =
let doc =
{| {table {tr {td some content} {td some other content}} {tr {td in another} {td row}}} |}
in

translate doc |> print_doc;
[%expect
{|
| some content | some other content |
| in another | row | |}]

let%expect_test "table2" =
let doc = {|
{t | z | f |
|:-----|---:|
| fse | e | }
|} in

translate doc |> print_doc;
[%expect {|
| z | f |
|:-|-:|
| fse | e | |}]

let%expect_test "problematic_translation" =
let doc = {| {table {tr {td {ul {li first item} {li second item}}}} } |} in

translate doc |> print_doc;
[%expect {|
| - first item - second item | |}]

let%expect_test "code_with_output" =
let doc = {| {@ocaml[foo][output {b foo}]} |} in

translate doc |> print_doc;
[%expect {|
```ocaml
foo
```
output **foo** |}]
Loading

0 comments on commit 7ea8e53

Please sign in to comment.