Skip to content

Commit 2c877a1

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 5ac1ffc commit 2c877a1

File tree

20 files changed

+294
-20
lines changed

20 files changed

+294
-20
lines changed

src/document/comment.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,7 @@ module Reference = struct
8484
| `InstanceVariable (p, f) ->
8585
render_unresolved (p :> t) ^ "." ^ InstanceVariableName.to_string f
8686
| `Label (p, f) -> render_unresolved (p :> t) ^ "." ^ LabelName.to_string f
87+
| `Asset (p, f) -> render_unresolved (p :> t) ^ "." ^ AssetName.to_string f
8788

8889
(* This is the entry point. *)
8990
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
@@ -143,3 +143,4 @@ module LabelName = SimpleName
143143
module PageName = SimpleName
144144
module DefName = SimpleName
145145
module LocalName = SimpleName
146+
module AssetName = SimpleName

src/model/names.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -99,3 +99,5 @@ module PageName : SimpleName
9999
module DefName : SimpleName
100100

101101
module LocalName : SimpleName
102+
103+
module AssetName : SimpleName

src/model/paths.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -935,6 +935,10 @@ module Reference = struct
935935
module Page = struct
936936
type t = Paths_types.Resolved_reference.page
937937
end
938+
939+
module Asset = struct
940+
type t = Paths_types.Resolved_reference.asset
941+
end
938942
end
939943

940944
type t = Paths_types.Reference.any
@@ -1016,4 +1020,8 @@ module Reference = struct
10161020
module Page = struct
10171021
type t = Paths_types.Reference.page
10181022
end
1023+
1024+
module Asset = struct
1025+
type t = Paths_types.Reference.asset
1026+
end
10191027
end

src/model/paths.mli

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -507,6 +507,10 @@ module rec Reference : sig
507507
type t = Paths_types.Resolved_reference.page
508508
end
509509

510+
module Asset : sig
511+
type t = Paths_types.Resolved_reference.asset
512+
end
513+
510514
type t = Paths_types.Resolved_reference.any
511515

512516
val identifier : t -> Identifier.t
@@ -588,6 +592,10 @@ module rec Reference : sig
588592
type t = Paths_types.Reference.page
589593
end
590594

595+
module Asset : sig
596+
type t = Paths_types.Reference.asset
597+
end
598+
591599
type t = Paths_types.Reference.any
592600

593601
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
@@ -290,6 +290,8 @@ module Identifier = struct
290290
type reference_label = label
291291

292292
type reference_page = page
293+
294+
type reference_asset = asset_file
293295
end
294296

295297
module rec Path : sig
@@ -516,6 +518,7 @@ module rec Reference : sig
516518
| `TInstanceVariable
517519
| `TLabel
518520
| `TPage
521+
| `TAsset
519522
| `TChildPage
520523
| `TChildModule
521524
| `TUnknown ]
@@ -704,8 +707,16 @@ module rec Reference : sig
704707
| `ClassType of signature * ClassTypeName.t
705708
| `Method of class_signature * MethodName.t
706709
| `InstanceVariable of class_signature * InstanceVariableName.t
707-
| `Label of label_parent * LabelName.t ]
710+
| `Label of label_parent * LabelName.t
711+
| `Asset of page * AssetName.t ]
708712
(** @canonical Odoc_model.Paths.Reference.t *)
713+
714+
type asset =
715+
[ `Resolved of Resolved_reference.asset
716+
| `Root of string * [ `TAsset ]
717+
| `Dot of label_parent * string
718+
| `Asset of page * AssetName.t ]
719+
(** @canonical Odoc_model.Paths.Reference.Asset.t *)
709720
end =
710721
Reference
711722

@@ -859,5 +870,8 @@ and Resolved_reference : sig
859870
| `InstanceVariable of class_signature * InstanceVariableName.t
860871
| `Label of label_parent * LabelName.t ]
861872
(** @canonical Odoc_model.Paths.Reference.Resolved.t *)
873+
874+
type asset = [ `Identifier of Identifier.reference_asset ]
875+
(** @canonical Odoc_model.Paths.Reference.Resolved.Asset.t *)
862876
end =
863877
Resolved_reference

src/model/reference.ml

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,7 @@ let match_extra_odoc_reference_kind (_location as loc) s :
7575
Some `TLabel
7676
| Some "module-type" -> Some `TModuleType
7777
| Some "page" -> Some `TPage
78+
| Some "asset" -> Some `TAsset
7879
| Some "value" ->
7980
d loc "value" "val";
8081
Some `TValue
@@ -323,6 +324,26 @@ let parse whole_reference_location s :
323324
|> Error.raise_exception)
324325
in
325326

327+
let page (kind, identifier, location) tokens : Page.t =
328+
let kind = match_reference_kind location kind in
329+
match tokens with
330+
| [] -> (
331+
match kind with
332+
| (`TUnknown | `TPage) as kind -> `Root (identifier, kind)
333+
| _ -> expected [ "page" ] location |> Error.raise_exception)
334+
| next_token :: tokens -> (
335+
match kind with
336+
| `TUnknown -> `Dot (label_parent next_token tokens, identifier)
337+
| _ ->
338+
let suggestion =
339+
Printf.sprintf "'page-%s' should be first." identifier
340+
in
341+
not_allowed ~what:"Page label"
342+
~in_what:"the last component of a reference path" ~suggestion
343+
location
344+
|> Error.raise_exception)
345+
in
346+
326347
let start_from_last_component (kind, identifier, location) old_kind tokens =
327348
let new_kind = match_reference_kind location kind in
328349
let kind =
@@ -385,6 +406,8 @@ let parse whole_reference_location s :
385406
| `TLabel ->
386407
`Label
387408
(label_parent next_token tokens, LabelName.make_std identifier)
409+
| `TAsset ->
410+
`Asset (page next_token tokens, AssetName.make_std identifier)
388411
| `TChildPage | `TChildModule ->
389412
let suggestion =
390413
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
@@ -194,6 +196,7 @@ module General_paths = struct
194196
| `TType -> C0 "`TType"
195197
| `TUnknown -> C0 "`TUnknown"
196198
| `TValue -> C0 "`TValue"
199+
| `TAsset -> C0 "`TValue"
197200
| `TChildPage -> C0 "`TChildPage"
198201
| `TChildModule -> C0 "`TChildModule")
199202

@@ -316,7 +319,9 @@ module General_paths = struct
316319
((x1 :> r), x2),
317320
Pair (reference, Names.instancevariablename) )
318321
| `Label (x1, x2) ->
319-
C ("`Label", ((x1 :> r), x2), Pair (reference, Names.labelname)))
322+
C ("`Label", ((x1 :> r), x2), Pair (reference, Names.labelname))
323+
| `Asset (x1, x2) ->
324+
C ("`Asset", ((x1 :> r), x2), Pair (reference, Names.assetname)))
320325

321326
and resolved_reference : rr t =
322327
Variant

src/xref2/component.ml

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

1453+
and model_resolved_asset_reference ppf
1454+
(`Identifier id : Odoc_model.Paths.Reference.Resolved.Asset.t) =
1455+
Format.fprintf ppf "%a" model_identifier
1456+
(id :> Odoc_model.Paths.Identifier.t)
1457+
14531458
and model_reference ppf (r : Odoc_model.Paths.Reference.t) =
14541459
let open Odoc_model.Paths.Reference in
14551460
match r with
@@ -1509,6 +1514,23 @@ module Fmt = struct
15091514
Format.fprintf ppf "%a.%s" model_reference
15101515
(parent :> t)
15111516
(LabelName.to_string name)
1517+
| `Asset (parent, name) ->
1518+
Format.fprintf ppf "%a.%s" model_reference
1519+
(parent :> t)
1520+
(AssetName.to_string name)
1521+
1522+
and model_asset_reference ppf (r : Odoc_model.Paths.Reference.Asset.t) =
1523+
let open Odoc_model.Paths.Reference in
1524+
match r with
1525+
| `Resolved r' ->
1526+
Format.fprintf ppf "r(%a)" model_resolved_asset_reference r'
1527+
| `Root (name, _) -> Format.fprintf ppf "unresolvedroot(%s)" name
1528+
| `Dot (parent, str) ->
1529+
Format.fprintf ppf "%a.%s" model_reference (parent :> t) str
1530+
| `Asset (parent, name) ->
1531+
Format.fprintf ppf "%a.%s" model_reference
1532+
(parent :> t)
1533+
(AssetName.to_string name)
15121534
end
15131535

15141536
module LocalIdents = struct

src/xref2/component.mli

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

626+
val model_resolved_asset_reference :
627+
Format.formatter -> Odoc_model.Paths.Reference.Resolved.Asset.t -> unit
628+
626629
val model_reference : Format.formatter -> Odoc_model.Paths.Reference.t -> unit
630+
631+
val model_asset_reference :
632+
Format.formatter -> Odoc_model.Paths.Reference.Asset.t -> unit
627633
end
628634

629635
module Of_Lang : sig

0 commit comments

Comments
 (0)