Skip to content

Commit 5352a6f

Browse files
committed
Introduce resolving of asset referencing
Reference can now be toward assets. When resolving them, look up the assets of the current page, and if not found, recurse in the parent page. Signed-off-by: Paul-Elliot <[email protected]>
1 parent 1eb8431 commit 5352a6f

File tree

20 files changed

+295
-21
lines changed

20 files changed

+295
-21
lines changed

src/document/comment.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -88,6 +88,7 @@ module Reference = struct
8888
| `InstanceVariable (p, f) ->
8989
render_unresolved (p :> t) ^ "." ^ InstanceVariableName.to_string f
9090
| `Label (p, f) -> render_unresolved (p :> t) ^ "." ^ LabelName.to_string f
91+
| `Asset (p, f) -> render_unresolved (p :> t) ^ "." ^ AssetName.to_string f
9192

9293
(* This is the entry point. *)
9394
let to_ir : ?text:Inline.t -> Reference.t -> Inline.t =

src/model/names.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -138,3 +138,4 @@ module LabelName = SimpleName
138138
module PageName = SimpleName
139139
module DefName = SimpleName
140140
module LocalName = SimpleName
141+
module AssetName = SimpleName

src/model/names.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,3 +101,5 @@ module PageName : SimpleName
101101
module DefName : SimpleName
102102

103103
module LocalName : SimpleName
104+
105+
module AssetName : SimpleName

src/model/paths.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1058,6 +1058,10 @@ module Reference = struct
10581058
module Page = struct
10591059
type t = Paths_types.Resolved_reference.page
10601060
end
1061+
1062+
module Asset = struct
1063+
type t = Paths_types.Resolved_reference.asset
1064+
end
10611065
end
10621066

10631067
type t = Paths_types.Reference.any
@@ -1143,4 +1147,8 @@ module Reference = struct
11431147
module Page = struct
11441148
type t = Paths_types.Reference.page
11451149
end
1150+
1151+
module Asset = struct
1152+
type t = Paths_types.Reference.asset
1153+
end
11461154
end

src/model/paths.mli

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -546,6 +546,10 @@ module rec Reference : sig
546546
type t = Paths_types.Resolved_reference.page
547547
end
548548

549+
module Asset : sig
550+
type t = Paths_types.Resolved_reference.asset
551+
end
552+
549553
type t = Paths_types.Resolved_reference.any
550554

551555
val identifier : t -> Identifier.t
@@ -631,6 +635,10 @@ module rec Reference : sig
631635
type t = Paths_types.Reference.page
632636
end
633637

638+
module Asset : sig
639+
type t = Paths_types.Reference.asset
640+
end
641+
634642
type t = Paths_types.Reference.any
635643

636644
type tag_any = Paths_types.Reference.tag_any

src/model/paths_types.ml

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -310,6 +310,8 @@ module Identifier = struct
310310
type reference_label = label
311311

312312
type reference_page = page
313+
314+
type reference_asset = asset_file
313315
end
314316

315317
module rec Path : sig
@@ -548,6 +550,7 @@ module rec Reference : sig
548550
| `TInstanceVariable
549551
| `TLabel
550552
| `TPage
553+
| `TAsset
551554
| `TChildPage
552555
| `TChildModule
553556
| `TUnknown ]
@@ -742,8 +745,16 @@ module rec Reference : sig
742745
| `ClassType of signature * ClassTypeName.t
743746
| `Method of class_signature * MethodName.t
744747
| `InstanceVariable of class_signature * InstanceVariableName.t
745-
| `Label of label_parent * LabelName.t ]
748+
| `Label of label_parent * LabelName.t
749+
| `Asset of page * AssetName.t ]
746750
(** @canonical Odoc_model.Paths.Reference.t *)
751+
752+
type asset =
753+
[ `Resolved of Resolved_reference.asset
754+
| `Root of string * [ `TAsset ]
755+
| `Dot of label_parent * string
756+
| `Asset of page * AssetName.t ]
757+
(** @canonical Odoc_model.Paths.Reference.Asset.t *)
747758
end =
748759
Reference
749760

@@ -908,5 +919,8 @@ and Resolved_reference : sig
908919
| `InstanceVariable of class_signature * InstanceVariableName.t
909920
| `Label of label_parent * LabelName.t ]
910921
(** @canonical Odoc_model.Paths.Reference.Resolved.t *)
922+
923+
type asset = [ `Identifier of Identifier.reference_asset ]
924+
(** @canonical Odoc_model.Paths.Reference.Resolved.Asset.t *)
911925
end =
912926
Resolved_reference

src/model/reference.ml

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,7 @@ let match_extra_odoc_reference_kind (_location as loc) s :
7676
Some `TLabel
7777
| Some "module-type" -> Some `TModuleType
7878
| Some "page" -> Some `TPage
79+
| Some "asset" -> Some `TAsset
7980
| Some "value" ->
8081
d loc "value" "val";
8182
Some `TValue
@@ -298,6 +299,26 @@ let parse whole_reference_location s :
298299
|> Error.raise_exception)
299300
in
300301

302+
let page (kind, identifier, location) tokens : Page.t =
303+
let kind = match_reference_kind location kind in
304+
match tokens with
305+
| [] -> (
306+
match kind with
307+
| (`TUnknown | `TPage) as kind -> `Root (identifier, kind)
308+
| _ -> expected [ "page" ] location |> Error.raise_exception)
309+
| next_token :: tokens -> (
310+
match kind with
311+
| `TUnknown -> `Dot (label_parent next_token tokens, identifier)
312+
| _ ->
313+
let suggestion =
314+
Printf.sprintf "'page-%s' should be first." identifier
315+
in
316+
not_allowed ~what:"Page label"
317+
~in_what:"the last component of a reference path" ~suggestion
318+
location
319+
|> Error.raise_exception)
320+
in
321+
301322
let start_from_last_component (kind, identifier, location) old_kind tokens =
302323
let new_kind = match_reference_kind location kind in
303324
let kind =
@@ -363,6 +384,8 @@ let parse whole_reference_location s :
363384
| `TLabel ->
364385
`Label
365386
(label_parent next_token tokens, LabelName.make_std identifier)
387+
| `TAsset ->
388+
`Asset (page next_token tokens, AssetName.make_std identifier)
366389
| `TChildPage | `TChildModule ->
367390
let suggestion =
368391
Printf.sprintf "'child-%s' should be first." identifier

src/model_desc/paths_desc.ml

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,8 @@ module Names = struct
3434

3535
let labelname = To_string LabelName.to_string
3636

37+
let assetname = To_string AssetName.to_string
38+
3739
let pagename = To_string PageName.to_string
3840

3941
let parametername = To_string ModuleName.to_string
@@ -200,6 +202,7 @@ module General_paths = struct
200202
| `TType -> C0 "`TType"
201203
| `TUnknown -> C0 "`TUnknown"
202204
| `TValue -> C0 "`TValue"
205+
| `TAsset -> C0 "`TValue"
203206
| `TChildPage -> C0 "`TChildPage"
204207
| `TChildModule -> C0 "`TChildModule")
205208

@@ -329,7 +332,9 @@ module General_paths = struct
329332
((x1 :> r), x2),
330333
Pair (reference, Names.instancevariablename) )
331334
| `Label (x1, x2) ->
332-
C ("`Label", ((x1 :> r), x2), Pair (reference, Names.labelname)))
335+
C ("`Label", ((x1 :> r), x2), Pair (reference, Names.labelname))
336+
| `Asset (x1, x2) ->
337+
C ("`Asset", ((x1 :> r), x2), Pair (reference, Names.assetname)))
333338

334339
and resolved_reference : rr t =
335340
Variant

src/xref2/component.ml

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1499,6 +1499,11 @@ module Fmt = struct
14991499
(parent :> t)
15001500
(LabelName.to_string name)
15011501

1502+
and model_resolved_asset_reference ppf
1503+
(`Identifier id : Odoc_model.Paths.Reference.Resolved.Asset.t) =
1504+
Format.fprintf ppf "%a" model_identifier
1505+
(id :> Odoc_model.Paths.Identifier.t)
1506+
15021507
and model_reference ppf (r : Odoc_model.Paths.Reference.t) =
15031508
let open Odoc_model.Paths.Reference in
15041509
match r with
@@ -1562,6 +1567,23 @@ module Fmt = struct
15621567
Format.fprintf ppf "%a.%s" model_reference
15631568
(parent :> t)
15641569
(LabelName.to_string name)
1570+
| `Asset (parent, name) ->
1571+
Format.fprintf ppf "%a.%s" model_reference
1572+
(parent :> t)
1573+
(AssetName.to_string name)
1574+
1575+
and model_asset_reference ppf (r : Odoc_model.Paths.Reference.Asset.t) =
1576+
let open Odoc_model.Paths.Reference in
1577+
match r with
1578+
| `Resolved r' ->
1579+
Format.fprintf ppf "r(%a)" model_resolved_asset_reference r'
1580+
| `Root (name, _) -> Format.fprintf ppf "unresolvedroot(%s)" name
1581+
| `Dot (parent, str) ->
1582+
Format.fprintf ppf "%a.%s" model_reference (parent :> t) str
1583+
| `Asset (parent, name) ->
1584+
Format.fprintf ppf "%a.%s" model_reference
1585+
(parent :> t)
1586+
(AssetName.to_string name)
15651587
end
15661588

15671589
module LocalIdents = struct

src/xref2/component.mli

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -636,7 +636,13 @@ module Fmt : sig
636636
val model_resolved_reference :
637637
Format.formatter -> Odoc_model.Paths.Reference.Resolved.t -> unit
638638

639+
val model_resolved_asset_reference :
640+
Format.formatter -> Odoc_model.Paths.Reference.Resolved.Asset.t -> unit
641+
639642
val model_reference : Format.formatter -> Odoc_model.Paths.Reference.t -> unit
643+
644+
val model_asset_reference :
645+
Format.formatter -> Odoc_model.Paths.Reference.Asset.t -> unit
640646
end
641647

642648
module Of_Lang : sig

0 commit comments

Comments
 (0)