Skip to content

Commit f1e9efa

Browse files
committed
WIP
1 parent 468ab02 commit f1e9efa

File tree

21 files changed

+412
-62
lines changed

21 files changed

+412
-62
lines changed

src/document/comment.ml

Lines changed: 46 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -121,9 +121,9 @@ module Reference = struct
121121
in
122122
match Url.from_identifier ~stop_before:false id with
123123
| Ok url ->
124-
let target = InternalLink.Resolved url in
125-
let link = { InternalLink.target; content; tooltip } in
126-
[ inline @@ Inline.InternalLink link ]
124+
let target = Target.Internal (Resolved url) in
125+
let link = { Link.target; content; tooltip } in
126+
[ inline @@ Inline.Link link ]
127127
| Error (Not_linkable _) -> content
128128
| Error exn ->
129129
(* FIXME: better error message *)
@@ -137,9 +137,9 @@ module Reference = struct
137137
[ inline @@ Inline.Source s ]
138138
| Some content ->
139139
let link =
140-
{ InternalLink.target = Unresolved; content; tooltip = Some s }
140+
{ Link.target = Internal Unresolved; content; tooltip = Some s }
141141
in
142-
[ inline @@ Inline.InternalLink link ])
142+
[ inline @@ Inline.Link link ])
143143
end
144144

145145
let leaf_inline_element : Comment.leaf_inline_element -> Inline.one = function
@@ -184,7 +184,7 @@ let rec inline_element : Comment.inline_element -> Inline.t = function
184184
| [] -> [ inline @@ Text target ]
185185
| _ -> non_link_inline_element_list content
186186
in
187-
[ inline @@ Link (target, content) ]
187+
[ inline @@ Link { target = External target; content; tooltip = None } ]
188188

189189
and inline_element_list elements =
190190
List.concat
@@ -277,6 +277,38 @@ let rec nestable_block_element :
277277
and raise warnings *)
278278
in
279279
[ block @@ Table { data; align } ]
280+
| `Media (href, media, content) ->
281+
let content =
282+
match (content, href) with
283+
| [], `Reference path ->
284+
let s = Reference.render_unresolved (path :> Comment.Reference.t) in
285+
[ inline @@ Inline.Source (source_of_code s) ]
286+
| [], `Link href -> [ inline @@ Inline.Source (source_of_code href) ]
287+
| _ -> inline_element_list content
288+
in
289+
let url =
290+
match href with
291+
| `Reference (`Resolved r) -> (
292+
let id =
293+
Odoc_model.Paths.Reference.Resolved.(identifier (r :> t))
294+
in
295+
match Url.from_identifier ~stop_before:false id with
296+
| Ok url -> Target.Internal (Resolved url)
297+
| Error exn ->
298+
(* FIXME: better error message *)
299+
Printf.eprintf "Id.href failed: %S\n%!"
300+
(Url.Error.to_string exn);
301+
Internal Unresolved)
302+
| `Reference _ -> Internal Unresolved
303+
| `Link href -> External href
304+
in
305+
let i =
306+
match media with
307+
| `Audio -> Block.Audio (url, content)
308+
| `Video -> Video (url, content)
309+
| `Image -> Image (url, content)
310+
in
311+
[ block i ]
280312

281313
and paragraph : Comment.paragraph -> Block.one = function
282314
| [ { value = `Raw_markup (target, s); _ } ] ->
@@ -322,7 +354,14 @@ let tag : Comment.tag -> Description.one =
322354
| `See (kind, target, content) ->
323355
let value =
324356
match kind with
325-
| `Url -> mk_value (Inline.Link (target, [ inline @@ Text target ]))
357+
| `Url ->
358+
mk_value
359+
(Inline.Link
360+
{
361+
target = External target;
362+
content = [ inline @@ Text target ];
363+
tooltip = None;
364+
})
326365
| `File -> mk_value (Inline.Source (source_of_code target))
327366
| `Document -> mk_value (Inline.Text target)
328367
in

src/document/doctree.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -65,9 +65,7 @@ end = struct
6565
| Entity _ as t -> return t
6666
| Linebreak as t -> return t
6767
| Styled (st, content) -> return (Styled (st, remove_links content))
68-
| Link (_, t) -> t
69-
| InternalLink { target = Resolved _; content = t; _ } -> t
70-
| InternalLink { target = Unresolved; content = t; _ } -> t
68+
| Link { target = _; content = t; _ } -> t
7169
| Source l ->
7270
let rec f = function
7371
| Source.Elt t -> Source.Elt (remove_links t)
@@ -382,6 +380,9 @@ end = struct
382380
fun x ->
383381
match x.desc with
384382
| Inline x -> inline x
383+
| Audio (_, x) -> inline x
384+
| Video (_, x) -> inline x
385+
| Image (_, x) -> inline x
385386
| Paragraph x -> inline x
386387
| List (_, x) -> List.exists block x
387388
| Table { data; align = _ } ->
@@ -400,8 +401,7 @@ end = struct
400401
fun x ->
401402
match x.desc with
402403
| Styled (_, x) -> inline x
403-
| Link (_, x) -> inline x
404-
| InternalLink x -> inline x.content
404+
| Link { content = t; _ } -> inline t
405405
| Math _ -> true
406406
| Text _ | Entity _ | Linebreak | Source _ | Raw_markup _ -> false
407407
in

src/document/generator.ml

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -33,14 +33,14 @@ let type_var tv = tag "type-var" (O.txt tv)
3333
let enclose ~l ~r x = O.span (O.txt l ++ x ++ O.txt r)
3434

3535
let resolved p content =
36-
let link = { InternalLink.target = Resolved p; content; tooltip = None } in
37-
O.elt [ inline @@ InternalLink link ]
36+
let link = { Link.target = Internal (Resolved p); content; tooltip = None } in
37+
O.elt [ inline @@ Link link ]
3838

3939
let path p content = resolved (Url.from_path p) content
4040

4141
let unresolved content =
42-
let link = { InternalLink.target = Unresolved; content; tooltip = None } in
43-
O.elt [ inline @@ InternalLink link ]
42+
let link = { Link.target = Internal Unresolved; content; tooltip = None } in
43+
O.elt [ inline @@ Link link ]
4444

4545
let path_to_id path =
4646
match Url.Anchor.from_identifier (path :> Paths.Identifier.t) with
@@ -1841,8 +1841,7 @@ module Make (Syntax : SYNTAX) = struct
18411841
let li ?(attr = []) name url =
18421842
let link url desc =
18431843
let content = [ Inline.{ attr = []; desc } ] and tooltip = None in
1844-
Inline.InternalLink
1845-
{ InternalLink.target = Resolved url; content; tooltip }
1844+
Inline.Link { target = Internal (Resolved url); content; tooltip }
18461845
in
18471846
[ block ~attr @@ Block.Inline (inline @@ link url (Text name)) ]
18481847
in

src/document/types.ml

Lines changed: 15 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -5,12 +5,19 @@ module rec Class : sig
55
end =
66
Class
77

8-
and InternalLink : sig
9-
type target = Resolved of Url.t | Unresolved
8+
and Link : sig
9+
type t = { target : Target.t; content : Inline.t; tooltip : string option }
10+
end =
11+
Link
12+
13+
and Target : sig
14+
type internal = Resolved of Url.t | Unresolved
15+
16+
type href = string
1017

11-
type t = { target : target; content : Inline.t; tooltip : string option }
18+
type t = Internal of internal | External of href
1219
end =
13-
InternalLink
20+
Target
1421

1522
and Raw_markup : sig
1623
type target = Odoc_model.Comment.raw_markup_target
@@ -36,8 +43,6 @@ end =
3643
and Inline : sig
3744
type entity = string
3845

39-
type href = string
40-
4146
type t = one list
4247

4348
and one = { attr : Class.t; desc : desc }
@@ -47,8 +52,7 @@ and Inline : sig
4752
| Entity of entity
4853
| Linebreak
4954
| Styled of style * t
50-
| Link of href * t
51-
| InternalLink of InternalLink.t
55+
| Link of Link.t
5256
| Source of Source.t
5357
| Math of Math.t
5458
| Raw_markup of Raw_markup.t
@@ -90,6 +94,9 @@ and Block : sig
9094
| Verbatim of string
9195
| Raw_markup of Raw_markup.t
9296
| Table of t Table.t
97+
| Image of Target.t * Inline.t
98+
| Video of Target.t * Inline.t
99+
| Audio of Target.t * Inline.t
93100

94101
and list_type = Ordered | Unordered
95102
end =

src/document/utils.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,7 @@ and compute_length_inline (t : Types.Inline.t) : int =
3333
| Text s -> acc + String.length s
3434
| Entity _e -> acc + 1
3535
| Linebreak -> 0 (* TODO *)
36-
| Styled (_, t) | Link (_, t) | InternalLink { content = t; _ } ->
37-
acc + compute_length_inline t
36+
| Styled (_, t) | Link { content = t; _ } -> acc + compute_length_inline t
3837
| Source s -> acc + compute_length_source s
3938
| Math _ -> assert false
4039
| Raw_markup _ -> assert false

src/html/generator.ml

Lines changed: 78 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,12 @@
1313
* ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
1414
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
1515
*)
16-
16+
module HLink = Link
1717
open Odoc_document.Types
1818
module Html = Tyxml.Html
1919
module Doctree = Odoc_document.Doctree
2020
module Url = Odoc_document.Url
21+
module Link = HLink
2122

2223
type any = Html_types.flow5
2324

@@ -96,12 +97,12 @@ and styled style ~emph_level =
9697
| `Superscript -> (emph_level, Html.sup ~a:[])
9798
| `Subscript -> (emph_level, Html.sub ~a:[])
9899

99-
let rec internallink ~config ~emph_level ~resolve ?(a = [])
100-
{ InternalLink.target; content; tooltip } =
100+
let rec internallink ~config ~emph_level ~resolve ?(a = []) target content
101+
tooltip =
101102
let a = match tooltip with Some s -> Html.a_title s :: a | None -> a in
102103
let elt =
103104
match target with
104-
| Resolved uri ->
105+
| Target.Resolved uri ->
105106
let href = Link.href ~config ~resolve uri in
106107
let content = inline_nolink ~emph_level content in
107108
if Config.search_result config then
@@ -137,16 +138,17 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) :
137138
| Styled (style, c) ->
138139
let emph_level, app_style = styled style ~emph_level in
139140
[ app_style @@ inline ~config ~emph_level ~resolve c ]
140-
| Link (_, c) when Config.search_result config ->
141+
| Link { content = c; _ } when Config.search_result config ->
141142
(* When displaying for a search result, links are displayed as regular
142143
text. *)
143144
let content = inline_nolink ~emph_level c in
144145
[ Html.span ~a content ]
145-
| Link (href, c) ->
146+
| Link { target = External href; content = c; _ } ->
146147
let a = (a :> Html_types.a_attrib Html.attrib list) in
147148
let content = inline_nolink ~emph_level c in
148149
[ Html.a ~a:(Html.a_href href :: a) content ]
149-
| InternalLink c -> internallink ~config ~emph_level ~resolve ~a c
150+
| Link { target = Internal t; content; tooltip } ->
151+
internallink ~config ~emph_level ~resolve ~a t content tooltip
150152
| Source c -> source (inline ~config ~emph_level ~resolve) ~a c
151153
| Math s -> [ inline_math s ]
152154
| Raw_markup r -> raw_markup r
@@ -168,7 +170,6 @@ and inline_nolink ?(emph_level = 0) (l : Inline.t) :
168170
let emph_level, app_style = styled style ~emph_level in
169171
[ app_style @@ inline_nolink ~emph_level c ]
170172
| Link _ -> assert false
171-
| InternalLink _ -> assert false
172173
| Source c -> source (inline_nolink ~emph_level) ~a c
173174
| Math s -> [ inline_math s ]
174175
| Raw_markup r -> raw_markup r
@@ -206,6 +207,26 @@ let text_align = function
206207

207208
let cell_kind = function `Header -> Html.th | `Data -> Html.td
208209

210+
(* Turns an inline into a string, for use as alternative text in
211+
images *)
212+
let rec alt_of_inline (i : Inline.t) =
213+
let rec alt_of_source s =
214+
List.map
215+
(function
216+
| Source.Elt i -> alt_of_inline i | Tag (_, t) -> alt_of_source t)
217+
s
218+
|> String.concat ""
219+
in
220+
let alt_of_one (o : Inline.one) =
221+
match o.desc with
222+
| Text t | Math t | Entity t -> t
223+
| Linebreak -> "\n"
224+
| Styled (_, i) | Link { content = i; _ } -> alt_of_inline i
225+
| Source s -> alt_of_source s
226+
| Raw_markup _ -> ""
227+
in
228+
List.map alt_of_one i |> String.concat ""
229+
209230
let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
210231
let as_flow x = (x : phrasing Html.elt list :> flow Html.elt list) in
211232
let one (t : Block.one) =
@@ -243,6 +264,55 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
243264
let extra_class = [ "language-" ^ lang_tag ] in
244265
mk_block ~extra_class Html.pre (source (inline ~config ~resolve) c)
245266
| Math s -> mk_block Html.div [ block_math s ]
267+
| Audio (target, content) ->
268+
let content = inline ~config ~resolve content in
269+
let audio src = [ Html.audio ~src ~a:[ Html.a_controls () ] [] ] in
270+
let block =
271+
match target with
272+
| External url -> audio url
273+
| Internal (Resolved uri) ->
274+
let url = Link.href ~config ~resolve uri in
275+
audio url
276+
| Internal Unresolved ->
277+
let a = Html.a_class [ "xref-unresolved" ] :: [] in
278+
[ Html.span ~a content ]
279+
in
280+
mk_block Html.div block
281+
| Video (target, content) ->
282+
let content = inline ~config ~resolve content in
283+
let video src = [ Html.video ~src ~a:[ Html.a_controls () ] [] ] in
284+
let block =
285+
match target with
286+
| External url -> video url
287+
| Internal (Resolved uri) ->
288+
let url = Link.href ~config ~resolve uri in
289+
video url
290+
| Internal Unresolved ->
291+
let a = [ Html.a_class [ "xref-unresolved" ] ] in
292+
[ Html.span ~a content ]
293+
in
294+
mk_block Html.div block
295+
| Image (target, alt) ->
296+
let image src =
297+
let alt = alt_of_inline alt in
298+
let img =
299+
Html.a
300+
~a:[ Html.a_href src; Html.a_class [ "img-link" ] ]
301+
[ Html.img ~src ~alt () ]
302+
in
303+
[ img ]
304+
in
305+
let block =
306+
match target with
307+
| External url -> image url
308+
| Internal (Resolved uri) ->
309+
let url = Link.href ~config ~resolve uri in
310+
image url
311+
| Internal Unresolved ->
312+
let a = [ Html.a_class [ "xref-unresolved" ] ] in
313+
[ Html.span ~a (inline ~config ~resolve alt) ]
314+
in
315+
mk_block Html.div block
246316
in
247317
Odoc_utils.List.concat_map l ~f:one
248318

src/html/html_source.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
1+
module HLink = Link
12
open Odoc_document.Types
23
open Tyxml
4+
module Link = HLink
35

46
let html_of_doc ~config ~resolve docs =
57
let open Html in

src/html_support_files/odoc.css

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -448,7 +448,7 @@ a {
448448
color: inherit;
449449
}
450450

451-
a:hover {
451+
a:hover:not(.img-link) {
452452
box-shadow: 0 1px 0 0 var(--link-color);
453453
}
454454

src/model/comment.ml

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@ type style = [ `Bold | `Italic | `Emphasis | `Superscript | `Subscript ]
88

99
type alignment = [ `Left | `Center | `Right ]
1010

11+
type media = [ `Image | `Audio | `Video ]
12+
1113
type raw_markup_target = string
1214

1315
type leaf_inline_element =
@@ -52,6 +54,10 @@ type 'a abstract_table = {
5254
align : alignment option list option;
5355
}
5456

57+
type media_href = [ `Link of string | `Reference of Reference.Asset.t ]
58+
59+
type media_element = [ `Media of media_href * media * paragraph ]
60+
5561
type nestable_block_element =
5662
[ `Paragraph of paragraph
5763
| `Code_block of
@@ -64,7 +70,7 @@ type nestable_block_element =
6470
| `Table of nestable_block_element abstract_table
6571
| `List of
6672
[ `Unordered | `Ordered ] * nestable_block_element with_location list list
67-
]
73+
| media_element ]
6874

6975
type tag =
7076
[ `Author of string

0 commit comments

Comments
 (0)