Skip to content

Commit efe2e0e

Browse files
committed
WIP
1 parent f1e9efa commit efe2e0e

File tree

13 files changed

+155
-18
lines changed

13 files changed

+155
-18
lines changed

src/document/sidebar.ml

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -68,9 +68,8 @@ type t = { pages : pages list; libraries : library list }
6868
let of_lang (v : Odoc_model.Lang.Sidebar.t) =
6969
let sidebar_toc_entry id content =
7070
let href = id |> Url.Path.from_identifier |> Url.from_path in
71-
let target = InternalLink.Resolved href in
72-
let link = { InternalLink.target; content; tooltip = None } in
73-
inline @@ Inline.InternalLink link
71+
let target = Target.Internal (Resolved href) in
72+
inline @@ Inline.Link { target; content; tooltip = None }
7473
in
7574
let pages =
7675
let page_hierarchy { Odoc_model.Lang.Sidebar.page_name; pages } =

src/latex/generator.ml

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -219,13 +219,13 @@ let source k (t : Source.t) =
219219
and tokens t = Odoc_utils.List.concat_map t ~f:token in
220220
tokens t
221221

222-
let rec internalref ~verbatim ~in_source (t : InternalLink.t) =
222+
let rec internalref ~verbatim ~in_source (t : Target.internal) (c : Inline.t) =
223223
let target =
224-
match t.target with
225-
| InternalLink.Resolved uri -> Link.label uri
224+
match t with
225+
| Target.Resolved uri -> Link.label uri
226226
| Unresolved -> "xref-unresolved"
227227
in
228-
let text = Some (inline ~verbatim ~in_source t.content) in
228+
let text = Some (inline ~verbatim ~in_source c) in
229229
let short = in_source in
230230
Internal_ref { short; target; text }
231231

@@ -235,10 +235,11 @@ and inline ~in_source ~verbatim (l : Inline.t) =
235235
| Text _s -> assert false
236236
| Linebreak -> [ Break Line ]
237237
| Styled (style, c) -> [ Style (style, inline ~verbatim ~in_source c) ]
238-
| Link (ext, c) ->
238+
| Link { target = External ext; content = c; _ } ->
239239
let content = inline ~verbatim:false ~in_source:false c in
240240
[ External_ref (ext, Some content) ]
241-
| InternalLink c -> [ internalref ~in_source ~verbatim c ]
241+
| Link { target = Internal ref_; content = c; _ } ->
242+
[ internalref ~in_source ~verbatim ref_ c ]
242243
| Source c ->
243244
[ Inlined_code (source (inline ~verbatim:false ~in_source:true) c) ]
244245
| Math s -> [ Raw (Format.asprintf "%a" Raw.math s) ]
@@ -280,6 +281,9 @@ let rec block ~in_source (l : Block.t) =
280281
let one (t : Block.one) =
281282
match t.desc with
282283
| Inline i -> inline ~verbatim:false ~in_source:false i
284+
| Audio (_, content) | Video (_, content) | Image (_, content) ->
285+
inline ~verbatim:false ~in_source:false content
286+
@ if in_source then [] else [ Break Paragraph ]
283287
| Paragraph i ->
284288
inline ~in_source:false ~verbatim:false i
285289
@ if in_source then [] else [ Break Paragraph ]

src/manpage/generator.ml

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
1+
module ManLink = Link
12
open Odoc_document
23
open Types
34
open Doctree
5+
module Link = ManLink
46

57
(*
68
Manpages relies on the (g|t|n)roff document language.
@@ -247,7 +249,7 @@ let strip l =
247249
{ h with desc = Styled (sty, List.rev @@ loop [] content) }
248250
in
249251
loop (h :: acc) t
250-
| Link (_, content) | InternalLink { content; _ } ->
252+
| Link { content; _ } ->
251253
let acc = loop acc content in
252254
loop acc t
253255
| Source code ->
@@ -303,9 +305,9 @@ and inline (l : Inline.t) =
303305
x ++ inline rest
304306
| Linebreak -> break ++ inline rest
305307
| Styled (sty, content) -> style sty (inline content) ++ inline rest
306-
| Link (href, content) ->
308+
| Link { target = External href; content; _ } ->
307309
env "UR" "UE" href (inline @@ strip content) ++ inline rest
308-
| InternalLink { content; _ } ->
310+
| Link { content; _ } ->
309311
font "CI" (inline @@ strip content) ++ inline rest
310312
| Source content -> source_code content ++ inline rest
311313
| Math s -> math s ++ inline rest
@@ -365,6 +367,8 @@ let rec block (l : Block.t) =
365367
let continue r = if r = [] then noop else vspace ++ block r in
366368
match b.desc with
367369
| Inline i -> inline i ++ continue rest
370+
| Video (_, content) | Audio (_, content) | Image (_, content) ->
371+
inline content ++ continue rest
368372
| Paragraph i -> inline i ++ continue rest
369373
| List (list_typ, l) ->
370374
let f n b =

src/model/paths.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1182,6 +1182,10 @@ module Reference = struct
11821182
type t = Paths_types.Reference.page
11831183
end
11841184

1185+
module Asset = struct
1186+
type t = Paths_types.Reference.asset
1187+
end
1188+
11851189
module Hierarchy = struct
11861190
type t = Paths_types.Reference.hierarchy
11871191
end

src/model/paths.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -640,6 +640,10 @@ module rec Reference : sig
640640
type t = Paths_types.Reference.page
641641
end
642642

643+
module Asset : sig
644+
type t = Paths_types.Reference.asset
645+
end
646+
643647
module Hierarchy : sig
644648
type t = Paths_types.Reference.hierarchy
645649
end

src/model/paths_types.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -652,7 +652,8 @@ module rec Reference : sig
652652
| `Type of signature * TypeName.t ]
653653
(** @canonical Odoc_model.Paths.Reference.LabelParent.t *)
654654

655-
type asset = [ `Asset_path of hierarchy ]
655+
type asset =
656+
[ `Resolved of Resolved_reference.asset | `Asset_path of hierarchy ]
656657

657658
type module_ =
658659
[ `Resolved of Resolved_reference.module_

src/model/semantics.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -302,10 +302,10 @@ let rec nestable_block_element :
302302
let asset_ref_of_ref :
303303
Paths.Reference.t -> (Paths.Reference.Asset.t, _) Result.result =
304304
function
305-
| `Asset _ as a -> Result.Ok a
306-
| `Root (_, `TAsset) as a -> Ok a
307-
| `Root (s, `TUnknown) -> Ok (`Root (s, `TAsset))
308-
| `Dot (p, s) -> Ok (`Dot (p, s))
305+
| `Asset_path _ as a -> Result.Ok a
306+
(* | `Root (_, `TAsset) as a -> Ok a *)
307+
(* | `Root (s, `TUnknown) -> Ok (`Root (s, `TAsset)) *)
308+
(* | `Dot (p, s) -> Ok (`Dot (p, s)) *)
309309
| _ ->
310310
Error
311311
(not_allowed ~suggestion:"Use a reference to an asset"

src/search/entry.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -137,6 +137,7 @@ and entries_of_doc id d =
137137
| `Verbatim _ -> [ entry ~id ~doc:[ d ] ~kind:(Doc Verbatim) ]
138138
| `Math_block _ -> [ entry ~id ~doc:[ d ] ~kind:(Doc MathBlock) ]
139139
| `Table _ -> []
140+
| `Media _ -> []
140141

141142
let entries_of_item (x : Odoc_model.Fold.item) =
142143
match x with

src/xref2/link.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -295,7 +295,7 @@ and comment_nestable_block_element env parent ~loc:_
295295
`Modules refs
296296
| `Media (`Reference r, m, content) as orig -> (
297297
match Ref_tools.resolve_asset_reference env r |> Error.raise_warnings with
298-
| Ok x -> `Media (`Reference (`Resolved x), m, content)
298+
| Ok (x, _) -> `Media (`Reference (`Resolved x), m, content)
299299
| Error e ->
300300
Errors.report
301301
~what:(`Reference (r :> Paths.Reference.t))

src/xref2/ref_tools.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -831,6 +831,11 @@ let resolved3 (r, _, _) = resolved1 r
831831

832832
and resolved2 (r, _) = resolved1 r
833833

834+
let resolve_asset_reference env (r : Reference.Asset.t) : Asset.t ref_result =
835+
match r with
836+
| `Resolved _r -> failwith "What's going on!?"
837+
| `Asset_path p -> Path.asset_in_env env p
838+
834839
let resolved_type_lookup = function
835840
| `T (r, _) -> resolved1 r
836841
| `C (r, _) -> resolved1 r
@@ -995,5 +1000,8 @@ let resolve_reference : _ -> Reference.t -> _ =
9951000
let resolve_module_reference env m =
9961001
Odoc_model.Error.catch_warnings (fun () -> resolve_module_reference env m)
9971002

1003+
let resolve_asset_reference env m =
1004+
Odoc_model.Error.catch_warnings (fun () -> resolve_asset_reference env m)
1005+
9981006
let resolve_reference env m =
9991007
Odoc_model.Error.catch_warnings (fun () -> resolve_reference env m)

0 commit comments

Comments
 (0)