Skip to content

Commit e38f414

Browse files
panglesdjonludlam
authored andcommitted
Adding constructors and datatypes to component path
Signed-off-by: Paul-Elliot <[email protected]>
1 parent 5826eb1 commit e38f414

File tree

6 files changed

+153
-0
lines changed

6 files changed

+153
-0
lines changed

src/xref2/component.ml

Lines changed: 96 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1034,13 +1034,39 @@ module Fmt = struct
10341034
Format.fprintf ppf "%a.%s" resolved_parent_path p
10351035
(Odoc_model.Names.TypeName.to_string t)
10361036

1037+
and resolved_datatype_path :
1038+
Format.formatter -> Cpath.Resolved.datatype -> unit =
1039+
fun ppf p ->
1040+
match p with
1041+
| `Local id -> Format.fprintf ppf "%a" Ident.fmt id
1042+
| `Gpath p ->
1043+
Format.fprintf ppf "%a" model_resolved_path
1044+
(p :> Odoc_model.Paths.Path.Resolved.t)
1045+
| `Substituted x ->
1046+
Format.fprintf ppf "substituted(%a)" resolved_datatype_path x
1047+
| `CanonicalDataType (t1, t2) ->
1048+
Format.fprintf ppf "canonicalty(%a,%a)" resolved_datatype_path t1
1049+
model_path
1050+
(t2 :> Odoc_model.Paths.Path.t)
1051+
| `Type (p, t) ->
1052+
Format.fprintf ppf "%a.%s" resolved_parent_path p
1053+
(Odoc_model.Names.TypeName.to_string t)
1054+
10371055
and resolved_value_path : Format.formatter -> Cpath.Resolved.value -> unit =
10381056
fun ppf p ->
10391057
match p with
10401058
| `Value (p, t) ->
10411059
Format.fprintf ppf "%a.%s" resolved_parent_path p
10421060
(Odoc_model.Names.ValueName.to_string t)
10431061

1062+
and resolved_constructor_path :
1063+
Format.formatter -> Cpath.Resolved.constructor -> unit =
1064+
fun ppf p ->
1065+
match p with
1066+
| `Constructor (p, t) ->
1067+
Format.fprintf ppf "%a.%s" resolved_datatype_path p
1068+
(Odoc_model.Names.ConstructorName.to_string t)
1069+
10441070
and resolved_parent_path : Format.formatter -> Cpath.Resolved.parent -> unit =
10451071
fun ppf p ->
10461072
match p with
@@ -1069,6 +1095,21 @@ module Fmt = struct
10691095
Format.fprintf ppf "%a.%s" resolved_parent_path p
10701096
(Odoc_model.Names.TypeName.to_string t)
10711097

1098+
and datatype_path : Format.formatter -> Cpath.datatype -> unit =
1099+
fun ppf p ->
1100+
match p with
1101+
| `Resolved r -> Format.fprintf ppf "r(%a)" resolved_datatype_path r
1102+
| `Identifier (id, b) ->
1103+
Format.fprintf ppf "identifier(%a, %b)" model_identifier
1104+
(id :> Odoc_model.Paths.Identifier.t)
1105+
b
1106+
| `Local (id, b) -> Format.fprintf ppf "local(%a,%b)" Ident.fmt id b
1107+
| `Substituted s -> Format.fprintf ppf "substituted(%a)" datatype_path s
1108+
| `Dot (m, s) -> Format.fprintf ppf "%a.%s" module_path m s
1109+
| `Type (p, t) ->
1110+
Format.fprintf ppf "%a.%s" resolved_parent_path p
1111+
(Odoc_model.Names.TypeName.to_string t)
1112+
10721113
and value_path : Format.formatter -> Cpath.value -> unit =
10731114
fun ppf p ->
10741115
match p with
@@ -1078,6 +1119,15 @@ module Fmt = struct
10781119
Format.fprintf ppf "%a.%s" resolved_parent_path p
10791120
(Odoc_model.Names.ValueName.to_string t)
10801121

1122+
and constructor_path : Format.formatter -> Cpath.constructor -> unit =
1123+
fun ppf p ->
1124+
match p with
1125+
| `Resolved r -> Format.fprintf ppf "r(%a)" resolved_constructor_path r
1126+
| `Dot (m, s) -> Format.fprintf ppf "%a.%s" datatype_path m s
1127+
| `Constructor (p, t) ->
1128+
Format.fprintf ppf "%a.%s" resolved_datatype_path p
1129+
(Odoc_model.Names.ConstructorName.to_string t)
1130+
10811131
and resolved_class_type_path :
10821132
Format.formatter -> Cpath.Resolved.class_type -> unit =
10831133
fun ppf p ->
@@ -1151,6 +1201,10 @@ module Fmt = struct
11511201
Format.fprintf ppf "%a.%s" model_resolved_path
11521202
(parent :> t)
11531203
(Odoc_model.Names.TypeName.to_string name)
1204+
| `Constructor (parent, name) ->
1205+
Format.fprintf ppf "%a.%s" model_resolved_path
1206+
(parent :> t)
1207+
(Odoc_model.Names.ConstructorName.to_string name)
11541208
| `Value (parent, name) ->
11551209
Format.fprintf ppf "%a.%s" model_resolved_path
11561210
(parent :> t)
@@ -1185,6 +1239,11 @@ module Fmt = struct
11851239
(t1 :> t)
11861240
model_path
11871241
(t2 :> Odoc_model.Paths.Path.t)
1242+
| `CanonicalDataType (t1, t2) ->
1243+
Format.fprintf ppf "canonicaldaty(%a,%a)" model_resolved_path
1244+
(t1 :> t)
1245+
model_path
1246+
(t2 :> Odoc_model.Paths.Path.t)
11881247
| `Apply (funct, arg) ->
11891248
Format.fprintf ppf "%a(%a)" model_resolved_path
11901249
(funct :> t)
@@ -1796,11 +1855,31 @@ module Of_Lang = struct
17961855
| `ClassType (p, name) ->
17971856
`ClassType (`Module (resolved_module_path ident_map p), name)
17981857

1858+
and resolved_datatype_path :
1859+
_ -> Odoc_model.Paths.Path.Resolved.DataType.t -> Cpath.Resolved.datatype
1860+
=
1861+
fun ident_map p ->
1862+
match p with
1863+
| `Identifier i -> (
1864+
match identifier Maps.Type.find ident_map.types i with
1865+
| `Local l -> `Local l
1866+
| `Identifier _ -> `Gpath p)
1867+
| `CanonicalDataType (p1, p2) ->
1868+
`CanonicalDataType (resolved_datatype_path ident_map p1, p2)
1869+
| `Type (p, name) -> `Type (`Module (resolved_module_path ident_map p), name)
1870+
17991871
and resolved_value_path :
18001872
_ -> Odoc_model.Paths.Path.Resolved.Value.t -> Cpath.Resolved.value =
18011873
fun ident_map (`Value (p, name)) ->
18021874
`Value (`Module (resolved_module_path ident_map p), name)
18031875

1876+
and resolved_constructor_path :
1877+
_ ->
1878+
Odoc_model.Paths.Path.Resolved.Constructor.t ->
1879+
Cpath.Resolved.constructor =
1880+
fun ident_map (`Constructor (p, name)) ->
1881+
`Constructor (resolved_datatype_path ident_map p, name)
1882+
18041883
and resolved_class_type_path :
18051884
_ ->
18061885
Odoc_model.Paths.Path.Resolved.ClassType.t ->
@@ -1859,6 +1938,23 @@ module Of_Lang = struct
18591938
| `Resolved r -> `Resolved (resolved_value_path ident_map r)
18601939
| `Dot (path', x) -> `Dot (module_path ident_map path', x)
18611940

1941+
and datatype : _ -> Odoc_model.Paths.Path.DataType.t -> Cpath.datatype =
1942+
fun ident_map p ->
1943+
match p with
1944+
| `Resolved r -> `Resolved (resolved_datatype_path ident_map r)
1945+
| `Identifier (i, b) -> (
1946+
match identifier Maps.Type.find ident_map.types i with
1947+
| `Identifier i -> `Identifier (i, b)
1948+
| `Local i -> `Local (i, b))
1949+
| `Dot (path', x) -> `Dot (module_path ident_map path', x)
1950+
1951+
and constructor_path :
1952+
_ -> Odoc_model.Paths.Path.Constructor.t -> Cpath.constructor =
1953+
fun ident_map p ->
1954+
match p with
1955+
| `Resolved r -> `Resolved (resolved_constructor_path ident_map r)
1956+
| `Dot (path', x) -> `Dot (datatype ident_map path', x)
1957+
18621958
and class_type_path :
18631959
_ -> Odoc_model.Paths.Path.ClassType.t -> Cpath.class_type =
18641960
fun ident_map p ->

src/xref2/component.mli

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -595,6 +595,8 @@ module Fmt : sig
595595

596596
val value_path : Format.formatter -> Cpath.value -> unit
597597

598+
val constructor_path : Format.formatter -> Cpath.constructor -> unit
599+
598600
val resolved_class_type_path :
599601
Format.formatter -> Cpath.Resolved.class_type -> unit
600602

@@ -659,6 +661,11 @@ module Of_Lang : sig
659661
val resolved_value_path :
660662
map -> Odoc_model.Paths.Path.Resolved.Value.t -> Cpath.Resolved.value
661663

664+
val resolved_constructor_path :
665+
map ->
666+
Odoc_model.Paths.Path.Resolved.Constructor.t ->
667+
Cpath.Resolved.constructor
668+
662669
val resolved_class_type_path :
663670
map ->
664671
Odoc_model.Paths.Path.Resolved.ClassType.t ->
@@ -671,8 +678,13 @@ module Of_Lang : sig
671678

672679
val type_path : map -> Odoc_model.Paths.Path.Type.t -> Cpath.type_
673680

681+
val datatype : map -> Odoc_model.Paths.Path.DataType.t -> Cpath.datatype
682+
674683
val value_path : map -> Odoc_model.Paths.Path.Value.t -> Cpath.value
675684

685+
val constructor_path :
686+
map -> Odoc_model.Paths.Path.Constructor.t -> Cpath.constructor
687+
676688
val class_type_path :
677689
map -> Odoc_model.Paths.Path.ClassType.t -> Cpath.class_type
678690

src/xref2/cpath.ml

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,15 @@ module rec Resolved : sig
3838

3939
and value = [ `Value of parent * ValueName.t ]
4040

41+
and datatype =
42+
[ `Local of Ident.path_datatype
43+
| `Gpath of Path.Resolved.DataType.t
44+
| `Substituted of datatype
45+
| `CanonicalDataType of datatype * Path.DataType.t
46+
| `Type of parent * TypeName.t ]
47+
48+
and constructor = [ `Constructor of datatype * ConstructorName.t ]
49+
4150
and class_type =
4251
[ `Local of Ident.path_class_type
4352
| `Substituted of class_type
@@ -82,6 +91,19 @@ and Cpath : sig
8291
| `Dot of module_ * string
8392
| `Value of Resolved.parent * ValueName.t ]
8493

94+
and datatype =
95+
[ `Resolved of Resolved.datatype
96+
| `Substituted of datatype
97+
| `Local of Ident.path_datatype * bool
98+
| `Identifier of Odoc_model.Paths.Identifier.Path.DataType.t * bool
99+
| `Dot of module_ * string
100+
| `Type of Resolved.parent * TypeName.t ]
101+
102+
and constructor =
103+
[ `Resolved of Resolved.constructor
104+
| `Dot of datatype * string
105+
| `Constructor of Resolved.datatype * ConstructorName.t ]
106+
85107
and class_type =
86108
[ `Resolved of Resolved.class_type
87109
| `Substituted of class_type

src/xref2/ident.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,8 @@ type class_type = [ `LClassType of ClassTypeName.t * int ]
5050

5151
type path_type = [ type_ | class_ | class_type ]
5252

53+
type path_datatype = type_
54+
5355
type path_value = value
5456

5557
type path_class_type = [ class_ | class_type ]

src/xref2/lang_of.ml

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -202,6 +202,21 @@ module Path = struct
202202
Odoc_model.Paths.Path.Resolved.Value.t =
203203
`Value (resolved_parent map p, name)
204204

205+
and resolved_datatype map (p : Cpath.Resolved.datatype) :
206+
Odoc_model.Paths.Path.Resolved.DataType.t =
207+
match p with
208+
| `Gpath y -> y
209+
| `Local id -> `Identifier (Component.TypeMap.find id map.type_)
210+
| `CanonicalDataType (t1, t2) ->
211+
`CanonicalDataType (resolved_datatype map t1, t2)
212+
| `Type (p, name) -> `Type (resolved_parent map p, name)
213+
| `Substituted s -> resolved_datatype map s
214+
215+
and resolved_constructor map
216+
(`Constructor (p, name) : Cpath.Resolved.constructor) :
217+
Odoc_model.Paths.Path.Resolved.Constructor.t =
218+
`Constructor (resolved_datatype map p, name)
219+
205220
and resolved_class_type map (p : Cpath.Resolved.class_type) :
206221
Odoc_model.Paths.Path.Resolved.ClassType.t =
207222
match p with

src/xref2/lang_of.mli

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,8 +29,14 @@ module Path : sig
2929

3030
val resolved_type : maps -> Cpath.Resolved.type_ -> Path.Resolved.Type.t
3131

32+
val resolved_datatype :
33+
maps -> Cpath.Resolved.datatype -> Path.Resolved.DataType.t
34+
3235
val resolved_value : maps -> Cpath.Resolved.value -> Path.Resolved.Value.t
3336

37+
val resolved_constructor :
38+
maps -> Cpath.Resolved.constructor -> Path.Resolved.Constructor.t
39+
3440
val resolved_class_type :
3541
maps -> Cpath.Resolved.class_type -> Path.Resolved.ClassType.t
3642

0 commit comments

Comments
 (0)