1
1
open Import
2
2
open Cmarkit
3
3
4
+ (* * TODO:
5
+
6
+ - Support meta from odoc-parser locations
7
+ - Add support for references *)
8
+
4
9
type t =
5
10
| Raw of string
6
11
| Markdown of string
@@ -141,36 +146,98 @@ and nestable_block_element_list_to_block nestables =
141
146
let blocks = List. map ~f: nestable_block_element_to_block nestables in
142
147
Block. Blocks (blocks, Meta. none)
143
148
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)
152
164
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)
171
178
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"
174
241
175
242
let rec block_element_to_block
176
243
(block_element :
@@ -182,9 +249,8 @@ let rec block_element_to_block
182
249
let meta = loc_to_meta location in
183
250
Block. Heading (heading, meta)
184
251
| Odoc_parser.Loc. { value = `Tag t ; location } ->
185
- let paragraph = tag_to_paragraph t in
186
252
let meta = loc_to_meta location in
187
- Block. Paragraph (paragraph, meta)
253
+ tag_to_block ~ meta t
188
254
| Odoc_parser.Loc.
189
255
{ value =
190
256
( `Paragraph _
@@ -197,7 +263,16 @@ let rec block_element_to_block
197
263
} as nestable -> nestable_block_element_to_block nestable
198
264
199
265
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
201
276
Block. Blocks (blocks, Meta. none)
202
277
203
278
let translate doc : t =
0 commit comments