Skip to content

Commit 2dbd106

Browse files
committed
Parse asset references
Signed-off-by: Paul-Elliot <[email protected]>
1 parent d211cb8 commit 2dbd106

File tree

9 files changed

+52
-1
lines changed

9 files changed

+52
-1
lines changed

src/document/comment.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,7 @@ module Reference = struct
7676
| `Root (n, _) -> n
7777
| `Dot (p, f) -> render_unresolved (p :> t) ^ "." ^ f
7878
| `Page_path p -> render_path p
79+
| `Asset_path p -> render_path p
7980
| `Module_path p -> render_path p
8081
| `Any_path p -> render_path p
8182
| `Module (p, f) ->

src/model/paths.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1091,6 +1091,10 @@ module Reference = struct
10911091
module Page = struct
10921092
type t = Paths_types.Resolved_reference.page
10931093
end
1094+
1095+
module Asset = struct
1096+
type t = Paths_types.Resolved_reference.asset
1097+
end
10941098
end
10951099

10961100
type t = Paths_types.Reference.any

src/model/paths.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -551,6 +551,10 @@ module rec Reference : sig
551551
type t = Paths_types.Resolved_reference.page
552552
end
553553

554+
module Asset : sig
555+
type t = Paths_types.Resolved_reference.asset
556+
end
557+
554558
type t = Paths_types.Resolved_reference.any
555559

556560
val identifier : t -> Identifier.t

src/model/paths_types.ml

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -575,6 +575,7 @@ module rec Reference : sig
575575
| `TInstanceVariable
576576
| `TLabel
577577
| `TPage
578+
| `TAsset
578579
| `TChildPage
579580
| `TChildModule
580581
| `TUnknown ]
@@ -651,6 +652,8 @@ module rec Reference : sig
651652
| `Type of signature * TypeName.t ]
652653
(** @canonical Odoc_model.Paths.Reference.LabelParent.t *)
653654

655+
type asset = [ `Asset_path of hierarchy ]
656+
654657
type module_ =
655658
[ `Resolved of Resolved_reference.module_
656659
| `Root of string * [ `TModule | `TUnknown ]
@@ -769,6 +772,7 @@ module rec Reference : sig
769772
| `Dot of label_parent * string
770773
| `Page_path of hierarchy
771774
| `Module_path of hierarchy
775+
| `Asset_path of hierarchy
772776
| `Any_path of hierarchy
773777
| `Module of signature * ModuleName.t
774778
| `ModuleType of signature * ModuleTypeName.t
@@ -929,6 +933,9 @@ and Resolved_reference : sig
929933
type page = [ `Identifier of Identifier.reference_page ]
930934
(** @canonical Odoc_model.Paths.Reference.Resolved.Page.t *)
931935

936+
type asset = [ `Identifier of Identifier.asset_file ]
937+
(** @canonical Odoc_model.Paths.Reference.Resolved.Asset.t *)
938+
932939
type any =
933940
[ `Identifier of Identifier.any
934941
| `Alias of Resolved_path.module_ * module_

src/model/reference.ml

Lines changed: 29 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -90,6 +90,7 @@ let match_extra_odoc_reference_kind (_location as loc) s :
9090
Some `TLabel
9191
| "module-type" -> Some `TModuleType
9292
| "page" -> Some `TPage
93+
| "asset" -> Some `TAsset
9394
| "value" ->
9495
d loc "value" "val";
9596
Some `TValue
@@ -352,12 +353,24 @@ let parse whole_reference_location s :
352353
)
353354
in
354355

356+
let label_parent_path { identifier; location; _ } kind next_token tokens =
357+
let path () = path [ identifier ] next_token tokens in
358+
match kind with
359+
| `TUnknown -> `Any_path (path ())
360+
| `TModule -> `Module_path (path ())
361+
| `TPage -> `Page_path (path ())
362+
| _ ->
363+
expected ~expect_paths:true [ "module"; "page" ] location
364+
|> Error.raise_exception
365+
in
366+
355367
let any_path { identifier; location; _ } kind next_token tokens =
356368
let path () = path [ identifier ] next_token tokens in
357369
match kind with
358370
| `TUnknown -> `Any_path (path ())
359371
| `TModule -> `Module_path (path ())
360372
| `TPage -> `Page_path (path ())
373+
| `TAsset -> `Asset_path (path ())
361374
| _ ->
362375
expected ~expect_paths:true [ "module"; "page" ] location
363376
|> Error.raise_exception
@@ -379,7 +392,7 @@ let parse whole_reference_location s :
379392
location
380393
|> Error.raise_exception)
381394
| next_token :: tokens when ends_in_slash next_token ->
382-
any_path token kind next_token tokens
395+
label_parent_path token kind next_token tokens
383396
| next_token :: tokens -> (
384397
match kind with
385398
| `TUnknown -> `Dot (label_parent next_token tokens, identifier)
@@ -499,6 +512,21 @@ let parse whole_reference_location s :
499512
in
500513
(* Prefixed pages are not differentiated. *)
501514
`Page_path (path [ identifier ] next_token tokens)
515+
| `TAsset ->
516+
let () =
517+
match next_token.kind with
518+
| `End_in_slash -> ()
519+
| `None | `Prefixed _ ->
520+
let suggestion =
521+
Printf.sprintf "Reference assets as '<parent_path>/%s'."
522+
identifier
523+
in
524+
not_allowed ~what:"Asset label"
525+
~in_what:"on the right side of a dot" ~suggestion location
526+
|> Error.raise_exception
527+
in
528+
(* Prefixed assets are not differentiated. *)
529+
`Asset_path (path [ identifier ] next_token tokens)
502530
| `TPathComponent -> assert false)
503531
in
504532

src/model_desc/paths_desc.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -202,6 +202,7 @@ module General_paths = struct
202202
| `TModule -> C0 "`TModule"
203203
| `TModuleType -> C0 "`TModuleType"
204204
| `TPage -> C0 "`TPage"
205+
| `TAsset -> C0 "`TAsset"
205206
| `TType -> C0 "`TType"
206207
| `TUnknown -> C0 "`TUnknown"
207208
| `TValue -> C0 "`TValue"
@@ -305,6 +306,7 @@ module General_paths = struct
305306
| `Root (x1, x2) -> C ("`Root", (x1, x2), Pair (string, reference_tag))
306307
| `Dot (x1, x2) -> C ("`Dot", ((x1 :> r), x2), Pair (reference, string))
307308
| `Page_path x -> C ("`Page_path", x, hierarchy_reference)
309+
| `Asset_path x -> C ("`Asset_path", x, hierarchy_reference)
308310
| `Module_path x -> C ("`Module_path", x, hierarchy_reference)
309311
| `Any_path x -> C ("`Any_path", x, hierarchy_reference)
310312
| `Module (x1, x2) ->

src/xref2/component.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1678,6 +1678,7 @@ module Fmt = struct
16781678
| `Dot (parent, str) ->
16791679
Format.fprintf ppf "%a.%s" (model_reference c) (parent :> t) str
16801680
| `Page_path p -> model_reference_hierarchy c ppf p
1681+
| `Asset_path p -> model_reference_hierarchy c ppf p
16811682
| `Module_path p -> model_reference_hierarchy c ppf p
16821683
| `Any_path p -> model_reference_hierarchy c ppf p
16831684
| `Module (parent, name) ->

src/xref2/errors.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ module Tools_error = struct
2020
| `Label
2121
| `Page_path
2222
| `Module_path
23+
| `Asset_path
2324
| `Any_path ]
2425

2526
type path_kind = [ `Page | `Unit ]
@@ -144,6 +145,7 @@ module Tools_error = struct
144145
| `Label -> "label"
145146
| `Page_path -> "path to a page"
146147
| `Module_path -> "path to a module"
148+
| `Asset_path -> "path to an asset"
147149
| `Any_path -> "path"
148150
in
149151
Format.pp_print_string fmt k

src/xref2/ref_tools.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -939,6 +939,7 @@ let resolve_reference : _ -> Reference.t -> _ =
939939
resolve_label_parent_reference env parent >>= fun p ->
940940
L.in_label_parent env p name >>= resolved_with_text
941941
| `Root (name, (`TPage | `TChildPage)) -> Page.in_env env name >>= resolved2
942+
| `Root (name, `TAsset) -> Error (`Find_by_name (`Asset_path, name))
942943
| `Dot (parent, name) -> resolve_reference_dot env parent name
943944
| `Root (name, `TConstructor) -> CS.in_env env name >>= resolved1
944945
| `Constructor (parent, name) ->
@@ -969,6 +970,7 @@ let resolve_reference : _ -> Reference.t -> _ =
969970
resolve_class_signature_reference env parent >>= fun p ->
970971
MV.in_class_signature env p name >>= resolved1
971972
| `Page_path p -> Path.page_in_env env p >>= resolved2
973+
| `Asset_path (tag, p) -> Error (`Path_error (`Not_found, tag, p))
972974
| `Module_path p ->
973975
Path.module_in_env env p
974976
>>= module_lookup_to_signature_lookup env

0 commit comments

Comments
 (0)