Skip to content

Commit 67d6b9b

Browse files
committed
Add support for tags
1 parent be7edb5 commit 67d6b9b

File tree

6 files changed

+156
-63
lines changed

6 files changed

+156
-63
lines changed

dune-project

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ possible and does not make any assumptions about IO.
5757
dune-build-info
5858
spawn
5959
cmarkit
60-
odoc-parser
60+
(odoc-parser (>= 2.0.0))
6161
(ppx_expect (and (>= v0.15.0) :with-test))
6262
(ocamlformat (and :with-test (= 0.24.1)))
6363
(ocamlc-loc (and (>= 3.5.0) (< 3.7.0)))

ocaml-lsp-server.opam

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ depends: [
3333
"dune-build-info"
3434
"spawn"
3535
"cmarkit"
36-
"odoc-parser"
36+
"odoc-parser" {>= "2.0.0"}
3737
"ppx_expect" {>= "v0.15.0" & with-test}
3838
"ocamlformat" {with-test & = "0.24.1"}
3939
"ocamlc-loc" {>= "3.5.0" & < "3.7.0"}

ocaml-lsp-server/src/doc_to_md.ml

Lines changed: 106 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,11 @@
11
open Import
22
open Cmarkit
33

4+
(** TODO:
5+
6+
- Support meta from odoc-parser locations
7+
- Add support for references *)
8+
49
type t =
510
| Raw of string
611
| Markdown of string
@@ -141,36 +146,98 @@ and nestable_block_element_list_to_block nestables =
141146
let blocks = List.map ~f:nestable_block_element_to_block nestables in
142147
Block.Blocks (blocks, Meta.none)
143148

144-
let tag_to_paragraph (tag : Odoc_parser.Ast.tag) =
145-
let format_tag tag text =
146-
Inline.Inlines
147-
( [ Inline.Strong_emphasis
148-
(Inline.Emphasis.make (Inline.Text (tag, Meta.none)), Meta.none)
149-
; Inline.Text (text, Meta.none)
150-
]
151-
, Meta.none )
149+
let strong_and_emphasis s =
150+
Inline.Emphasis
151+
( Inline.Emphasis.make
152+
(Inline.Strong_emphasis
153+
(Inline.Emphasis.make (Inline.Text (s, Meta.none)), Meta.none))
154+
, Meta.none )
155+
156+
let inline_code_span_of_string s =
157+
Inline.Code_span
158+
( Inline.Code_span.make ~backtick_count:1 (Block_line.tight_list_of_string s)
159+
, Meta.none )
160+
161+
let inline_link_of_string ~text uri =
162+
let ref =
163+
`Inline (Link_definition.make ~dest:(uri, Meta.none) (), Meta.none)
152164
in
153-
let tag, text =
154-
(* TODO: add support for tags *)
155-
match[@warning "-27"] tag with
156-
| `Author s -> ("@author", s)
157-
| `Deprecated text -> ("@deprecated", "")
158-
| `Param (id, text) -> ("@param", "")
159-
| `Raise (exc, text) -> ("@raise", "")
160-
| `Return text -> ("@return", "")
161-
| `See (`Url, url, text) -> ("@see", "")
162-
| `See (`File, filename, text) -> ("@see", "")
163-
| `See (`Document, document, text) -> ("@see", "")
164-
| `Since s -> ("@since", "")
165-
| `Before (version, text) -> ("@before", "")
166-
| `Version s -> ("@version", "")
167-
| `Canonical s -> ("@canonical", "")
168-
| `Inline -> ("@inline", "")
169-
| `Open -> ("@open", "")
170-
| `Closed -> ("@closed", "")
165+
Inline.Link (Inline.Link.make (Inline.Text (text, Meta.none)) ref, Meta.none)
166+
167+
let tag_to_block ~meta (tag : Odoc_parser.Ast.tag) =
168+
let format_tag_empty tag =
169+
Block.Paragraph (Block.Paragraph.make (strong_and_emphasis tag), Meta.none)
170+
in
171+
let format_tag_string tag text =
172+
let inline =
173+
Inline.Inlines
174+
( [ strong_and_emphasis tag; Inline.Text (" ", Meta.none); text ]
175+
, Meta.none )
176+
in
177+
Block.Paragraph (Block.Paragraph.make inline, meta)
171178
in
172-
let inline = format_tag tag text in
173-
Block.Paragraph.make inline
179+
let format_tag_block tag block =
180+
let prefix =
181+
Block.Paragraph (Block.Paragraph.make (strong_and_emphasis tag), Meta.none)
182+
in
183+
Block.Blocks ([ prefix; block ], meta)
184+
in
185+
let format_tag_string_with_block tag text block =
186+
let prefix =
187+
let inline =
188+
Inline.Inlines
189+
( [ strong_and_emphasis tag; Inline.Text (" ", Meta.none); text ]
190+
, Meta.none )
191+
in
192+
Block.Paragraph (Block.Paragraph.make inline, Meta.none)
193+
in
194+
Block.Blocks ([ prefix; block ], meta)
195+
in
196+
match tag with
197+
| `Author s ->
198+
let s = Inline.Text (s, Meta.none) in
199+
format_tag_string "@author" s
200+
| `Deprecated text ->
201+
let block = nestable_block_element_list_to_block text in
202+
format_tag_block "@deprecated" block
203+
| `Param (id, []) ->
204+
let id = Inline.Text (id, Meta.none) in
205+
format_tag_string "@param" id
206+
| `Param (id, text) ->
207+
let block = nestable_block_element_list_to_block text in
208+
let id = inline_code_span_of_string id in
209+
format_tag_string_with_block "@param" id block
210+
| `Raise (exc, text) ->
211+
let block = nestable_block_element_list_to_block text in
212+
let exc = inline_code_span_of_string exc in
213+
format_tag_string_with_block "@raise" exc block
214+
| `Return text ->
215+
let block = nestable_block_element_list_to_block text in
216+
format_tag_block "@return" block
217+
| `See (`Url, uri, text) ->
218+
let block = nestable_block_element_list_to_block text in
219+
let uri = inline_link_of_string ~text:"link" uri in
220+
format_tag_string_with_block "@see" uri block
221+
| `See ((`File | `Document), uri, text) ->
222+
let block = nestable_block_element_list_to_block text in
223+
let uri = inline_code_span_of_string uri in
224+
format_tag_string_with_block "@see" uri block
225+
| `Since version ->
226+
let version = inline_code_span_of_string version in
227+
format_tag_string "@since" version
228+
| `Before (version, text) ->
229+
let block = nestable_block_element_list_to_block text in
230+
let version = inline_code_span_of_string version in
231+
format_tag_string_with_block "@before" version block
232+
| `Version version ->
233+
let version = inline_code_span_of_string version in
234+
format_tag_string "@version" version
235+
| `Canonical { value = s; location = _ } ->
236+
let s = Inline.Text (s, Meta.none) in
237+
format_tag_string "@canonical" s
238+
| `Inline -> format_tag_empty "@inline"
239+
| `Open -> format_tag_empty "@open"
240+
| `Closed -> format_tag_empty "@closed"
174241

175242
let rec block_element_to_block
176243
(block_element :
@@ -182,9 +249,8 @@ let rec block_element_to_block
182249
let meta = loc_to_meta location in
183250
Block.Heading (heading, meta)
184251
| Odoc_parser.Loc.{ value = `Tag t; location } ->
185-
let paragraph = tag_to_paragraph t in
186252
let meta = loc_to_meta location in
187-
Block.Paragraph (paragraph, meta)
253+
tag_to_block ~meta t
188254
| Odoc_parser.Loc.
189255
{ value =
190256
( `Paragraph _
@@ -197,7 +263,16 @@ let rec block_element_to_block
197263
} as nestable -> nestable_block_element_to_block nestable
198264

199265
and block_element_list_to_block l =
200-
let blocks = List.map ~f:block_element_to_block l in
266+
let rec aux acc rest =
267+
match rest with
268+
| [] -> List.rev acc
269+
| el :: [] -> List.rev (block_element_to_block el :: acc)
270+
| el :: rest ->
271+
aux
272+
(Block.Blank_line ("", Meta.none) :: block_element_to_block el :: acc)
273+
rest
274+
in
275+
let blocks = aux [] l in
201276
Block.Blocks (blocks, Meta.none)
202277

203278
let translate doc : t =

ocaml-lsp-server/test/e2e/__tests__/ocamllsp-hoverExtended.ts

Lines changed: 13 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -219,24 +219,30 @@ describe("ocamllsp/hoverExtended", () => {
219219
This function has a nice documentation.
220220
221221
It performs division of two integer numbers.
222-
* * *
223-
***@param*** \`x\` dividend
222+
223+
***@param*** \`x\`
224+
dividend
224225
225226
***@param*** divisor
226227
227-
***@return*** *quotient*, i.e. result of division
228+
***@return***
229+
*quotient*, i.e. result of division
228230
229-
***@raise*** \`Division_by_zero\` raised when divided by zero
231+
***@raise*** \`Division_by_zero\`
232+
raised when divided by zero
230233
231-
***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_(%C3%B7,_or_/)) article
234+
***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_\\(%C3%B7,_or_/\\))
235+
article
232236
233-
***@see*** \`arithmetic.ml\` for more context
237+
***@see*** \`arithmetic.ml\`
238+
for more context
234239
235240
***@since*** \`4.0.0\`
236241
237242
***@before*** \`4.4.0\`
238243
239-
***@deprecated*** use \`(/)\`
244+
***@deprecated***
245+
use \`(/)\`
240246
241247
***@version*** \`1.0.0\`
242248

ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts

Lines changed: 13 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -258,24 +258,30 @@ describe("textDocument/hover", () => {
258258
This function has a nice documentation.
259259
260260
It performs division of two integer numbers.
261-
* * *
262-
***@param*** \`x\` dividend
261+
262+
***@param*** \`x\`
263+
dividend
263264
264265
***@param*** divisor
265266
266-
***@return*** *quotient*, i.e. result of division
267+
***@return***
268+
*quotient*, i.e. result of division
267269
268-
***@raise*** \`Division_by_zero\` raised when divided by zero
270+
***@raise*** \`Division_by_zero\`
271+
raised when divided by zero
269272
270-
***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_(%C3%B7,_or_/)) article
273+
***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_\\(%C3%B7,_or_/\\))
274+
article
271275
272-
***@see*** \`arithmetic.ml\` for more context
276+
***@see*** \`arithmetic.ml\`
277+
for more context
273278
274279
***@since*** \`4.0.0\`
275280
276281
***@before*** \`4.4.0\`
277282
278-
***@deprecated*** use \`(/)\`
283+
***@deprecated***
284+
use \`(/)\`
279285
280286
***@version*** \`1.0.0\`
281287

ocaml-lsp-server/test/e2e/__tests__/textDocument-signatureHelp.ts

Lines changed: 22 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -292,27 +292,33 @@ describe_opt("textDocument/completion", () => {
292292
This function has a nice documentation.
293293
294294
It performs division of two integer numbers.
295-
* * *
296-
***@param*** \`x\` dividend
297295
296+
***@param*** \`x\`
297+
dividend
298+
298299
***@param*** divisor
299-
300-
***@return*** *quotient*, i.e. result of division
301-
302-
***@raise*** \`Division_by_zero\` raised when divided by zero
303-
304-
***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_(%C3%B7,_or_/)) article
305-
306-
***@see*** \`arithmetic.ml\` for more context
307-
300+
301+
***@return***
302+
*quotient*, i.e. result of division
303+
304+
***@raise*** \`Division_by_zero\`
305+
raised when divided by zero
306+
307+
***@see*** [link](https://en.wikipedia.org/wiki/Arithmetic#Division_\\(%C3%B7,_or_/\\))
308+
article
309+
310+
***@see*** \`arithmetic.ml\`
311+
for more context
312+
308313
***@since*** \`4.0.0\`
309-
314+
310315
***@before*** \`4.4.0\`
311-
312-
***@deprecated*** use \`(/)\`
313-
316+
317+
***@deprecated***
318+
use \`(/)\`
319+
314320
***@version*** \`1.0.0\`
315-
321+
316322
***@author*** John Doe
317323
`,
318324
},

0 commit comments

Comments
 (0)