Skip to content

Commit 3960a58

Browse files
committed
Medias: make them nestable blocks
Signed-off-by: Paul-Elliot <[email protected]>
1 parent 1dbbda9 commit 3960a58

File tree

9 files changed

+160
-256
lines changed

9 files changed

+160
-256
lines changed

src/document/comment.ml

Lines changed: 32 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -264,6 +264,38 @@ let rec nestable_block_element :
264264
and raise warnings *)
265265
in
266266
[ block @@ Table { data; align } ]
267+
| `Media (href, media, content) ->
268+
let content =
269+
match (content, href) with
270+
| [], `Reference path ->
271+
let s = Reference.render_unresolved (path :> Comment.Reference.t) in
272+
[ inline @@ Inline.Source (source_of_code s) ]
273+
| [], `Link href -> [ inline @@ Inline.Source (source_of_code href) ]
274+
| _ -> inline_element_list content
275+
in
276+
let url =
277+
match href with
278+
| `Reference (`Resolved r) -> (
279+
let id =
280+
Odoc_model.Paths.Reference.Resolved.(identifier (r :> t))
281+
in
282+
match Url.from_identifier ~stop_before:false id with
283+
| Ok url -> Target.Internal (Resolved url)
284+
| Error exn ->
285+
(* FIXME: better error message *)
286+
Printf.eprintf "Id.href failed: %S\n%!"
287+
(Url.Error.to_string exn);
288+
Internal Unresolved)
289+
| `Reference _ -> Internal Unresolved
290+
| `Link href -> External href
291+
in
292+
let i =
293+
match media with
294+
| `Audio -> Block.Audio (url, content)
295+
| `Video -> Video (url, content)
296+
| `Image -> Image (url, content)
297+
in
298+
[ block i ]
267299

268300
and paragraph : Comment.paragraph -> Block.one = function
269301
| [ { value = `Raw_markup (target, s); _ } ] ->
@@ -338,38 +370,6 @@ let attached_block_element : Comment.attached_block_element -> Block.t =
338370
function
339371
| #Comment.nestable_block_element as e -> nestable_block_element e
340372
| `Tag t -> [ block ~attr:[ "at-tags" ] @@ Description [ tag t ] ]
341-
| `Media (href, media, content) ->
342-
let content =
343-
match (content, href) with
344-
| [], `Reference path ->
345-
let s = Reference.render_unresolved (path :> Comment.Reference.t) in
346-
[ inline @@ Inline.Source (source_of_code s) ]
347-
| [], `Link href -> [ inline @@ Inline.Source (source_of_code href) ]
348-
| _ -> inline_element_list content
349-
in
350-
let url =
351-
match href with
352-
| `Reference (`Resolved r) -> (
353-
let id =
354-
Odoc_model.Paths.Reference.Resolved.(identifier (r :> t))
355-
in
356-
match Url.from_identifier ~stop_before:false id with
357-
| Ok url -> Target.Internal (Resolved url)
358-
| Error exn ->
359-
(* FIXME: better error message *)
360-
Printf.eprintf "Id.href failed: %S\n%!"
361-
(Url.Error.to_string exn);
362-
Internal Unresolved)
363-
| `Reference _ -> Internal Unresolved
364-
| `Link href -> External href
365-
in
366-
let i =
367-
match media with
368-
| `Audio -> Block.Audio (url, content)
369-
| `Video -> Video (url, content)
370-
| `Image -> Image (url, content)
371-
in
372-
[ block i ]
373373

374374
(* TODO collaesce tags *)
375375

src/model/comment.ml

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,10 @@ type 'a abstract_table = {
5454
align : alignment option list option;
5555
}
5656

57+
type media_href = [ `Link of string | `Reference of Reference.Asset.t ]
58+
59+
type media_element = [ `Media of media_href * media * paragraph ]
60+
5761
type nestable_block_element =
5862
[ `Paragraph of paragraph
5963
| `Code_block of
@@ -66,7 +70,7 @@ type nestable_block_element =
6670
| `Table of nestable_block_element abstract_table
6771
| `List of
6872
[ `Unordered | `Ordered ] * nestable_block_element with_location list list
69-
]
73+
| media_element ]
7074

7175
type tag =
7276
[ `Author of string
@@ -93,12 +97,8 @@ type heading_level =
9397
| `Paragraph
9498
| `Subparagraph ]
9599

96-
type media_href = [ `Link of string | `Reference of Reference.Asset.t ]
97-
98-
type media_element = [ `Media of media_href * media * paragraph ]
99-
100100
type attached_block_element =
101-
[ nestable_block_element | media_element | `Tag of tag ]
101+
[ nestable_block_element | `Tag of tag ]
102102

103103
type heading_attrs = {
104104
heading_level : heading_level;
@@ -110,8 +110,7 @@ type block_element =
110110
[ nestable_block_element
111111
| `Heading of
112112
heading_attrs * Identifier.Label.t * inline_element with_location list
113-
| `Tag of tag
114-
| media_element ]
113+
| `Tag of tag]
115114

116115
type docs = block_element with_location list
117116

src/model/semantics.ml

Lines changed: 34 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -276,6 +276,39 @@ let rec nestable_block_element :
276276
grid
277277
in
278278
`Table { Comment.data; align } |> Location.at location
279+
| { value = `Media (_, { value = `Link href; _ }, content, m); location } ->
280+
let text = inline_elements status content in
281+
`Media (`Link href, m, text) |> Location.at location
282+
| {
283+
value =
284+
`Media
285+
(kind, { value = `Reference href; location = href_location }, content, m);
286+
location;
287+
} -> (
288+
match Error.raise_warnings (Reference.parse href_location href) with
289+
| Result.Ok target ->
290+
let text = inline_elements status content in
291+
let target =
292+
match target with
293+
| `Asset _ as a -> a
294+
| `Root (_, `TAsset) as a -> a
295+
| `Root (s, `TUnknown) -> `Root (s, `TAsset)
296+
| `Root _ -> failwith "a"
297+
| `Dot (_, s) -> failwith s
298+
| `Resolved _ -> failwith "todo2"
299+
| _ -> failwith "todo"
300+
in
301+
`Media (`Reference target, m, text) |> Location.at location
302+
| Result.Error error ->
303+
Error.raise_warning error;
304+
let placeholder =
305+
match kind with
306+
| `Simple -> `Code_span href
307+
| `With_text -> `Styled (`Emphasis, content)
308+
in
309+
`Paragraph
310+
(inline_elements status [ placeholder |> Location.at location ])
311+
|> Location.at location)
279312

280313
and nestable_block_elements status elements =
281314
List.map (nestable_block_element status) elements
@@ -483,62 +516,7 @@ let top_level_block_elements status ast_elements =
483516
in
484517
traverse ~top_heading_level
485518
(element :: comment_elements_acc)
486-
ast_elements
487-
| {
488-
value = `Media (_, { value = `Link href; _ }, content, m);
489-
location;
490-
} ->
491-
let text = inline_elements status content in
492-
let element =
493-
`Media (`Link href, m, text) |> Location.at location
494-
in
495-
traverse ~top_heading_level
496-
(element :: comment_elements_acc)
497-
ast_elements
498-
| {
499-
value =
500-
`Media
501-
( kind,
502-
{ value = `Reference href; location = href_location },
503-
content,
504-
m );
505-
location;
506-
} -> (
507-
match Error.raise_warnings (Reference.parse href_location href) with
508-
| Result.Ok target ->
509-
let text = inline_elements status content in
510-
let target =
511-
match target with
512-
| `Asset _ as a -> a
513-
| `Root (_, `TAsset) as a -> a
514-
| `Root (s, `TUnknown) -> `Root (s, `TAsset)
515-
| `Root _ -> failwith "a"
516-
| `Dot (_, s) -> failwith s
517-
| `Resolved _ -> failwith "todo2"
518-
| _ -> failwith "todo"
519-
in
520-
let element =
521-
`Media (`Reference target, m, text) |> Location.at location
522-
in
523-
traverse ~top_heading_level
524-
(element :: comment_elements_acc)
525-
ast_elements
526-
| Result.Error error ->
527-
Error.raise_warning error;
528-
let placeholder =
529-
match kind with
530-
| `Simple -> `Code_span href
531-
| `With_text -> `Styled (`Emphasis, content)
532-
in
533-
let placeholder =
534-
`Paragraph
535-
(inline_elements status
536-
[ placeholder |> Location.at location ])
537-
|> Location.at location
538-
in
539-
traverse ~top_heading_level
540-
(placeholder :: comment_elements_acc)
541-
ast_elements))
519+
ast_elements)
542520
in
543521
let top_heading_level =
544522
(* Non-page documents have a generated title. *)

src/parser/ast.ml

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,9 @@ type code_block_meta = {
4040
tags : string with_location option;
4141
}
4242

43+
type media = Token.media
44+
type media_href = Token.media_href
45+
4346
type code_block = {
4447
meta : code_block_meta option;
4548
delimiter : string option;
@@ -57,7 +60,12 @@ and nestable_block_element =
5760
* [ `Light | `Heavy ]
5861
* nestable_block_element with_location list list
5962
| `Table of table
60-
| `Math_block of string (** @since 2.0.0 *) ]
63+
| `Math_block of string (** @since 2.0.0 *)
64+
| `Media of
65+
reference_kind
66+
* media_href with_location
67+
* inline_element with_location list
68+
* media (** @since 2.3.0 *)]
6169
(** Some block elements may be nested within lists or tags, but not all.
6270
The [`List] constructor has a parameter of type [\[`Light | `Heavy\]].
6371
This corresponds to the syntactic constructor used (see the
@@ -89,17 +97,9 @@ type ocamldoc_tag =
8997
type tag = [ ocamldoc_tag | internal_tag ]
9098
type heading = int * string option * inline_element with_location list
9199

92-
type media = Token.media
93-
type media_href = Token.media_href
94-
95100
type block_element =
96101
[ nestable_block_element
97102
| `Heading of heading
98-
| `Tag of tag
99-
| `Media of
100-
reference_kind
101-
* media_href with_location
102-
* inline_element with_location list
103-
* media ]
103+
| `Tag of tag ]
104104

105105
type t = block_element with_location list

0 commit comments

Comments
 (0)