Skip to content

Commit 9eee684

Browse files
panglesdjonludlam
authored andcommitted
Adding support for resolving constructor and datatype
Signed-off-by: Paul-Elliot <[email protected]>
1 parent e38f414 commit 9eee684

File tree

7 files changed

+378
-6
lines changed

7 files changed

+378
-6
lines changed

src/xref2/compile.ml

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,17 @@ and value_path : Env.t -> Paths.Path.Value.t -> Paths.Path.Value.t =
3131
| Ok p' -> `Resolved Lang_of.(Path.resolved_value (empty ()) p')
3232
| Error _ -> p)
3333

34+
and constructor_path :
35+
Env.t -> Paths.Path.Constructor.t -> Paths.Path.Constructor.t =
36+
fun env p ->
37+
match p with
38+
| `Resolved _ -> p
39+
| _ -> (
40+
let cp = Component.Of_Lang.(constructor_path (empty ()) p) in
41+
match Tools.resolve_constructor_path env cp with
42+
| Ok p' -> `Resolved Lang_of.(Path.resolved_constructor (empty ()) p')
43+
| Error _ -> p)
44+
3445
and module_type_path :
3546
Env.t -> Paths.Path.ModuleType.t -> Paths.Path.ModuleType.t =
3647
fun env p ->

src/xref2/errors.ml

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,17 @@ module Tools_error = struct
7272
(* Could not find the module in the environment *)
7373
| `Parent of parent_lookup_error ]
7474

75+
and simple_datatype_lookup_error =
76+
[ `LocalDataType of
77+
Env.t * Ident.path_datatype
78+
(* Internal error: Found local path during lookup *)
79+
| `Find_failure
80+
(* Internal error: the type was not found in the parent signature *)
81+
| `Lookup_failureT of
82+
Identifier.Path.Type.t
83+
(* Could not find the module in the environment *)
84+
| `Parent of parent_lookup_error ]
85+
7586
and simple_value_lookup_error =
7687
[ `LocalValue of
7788
Env.t * Ident.path_value
@@ -83,6 +94,17 @@ module Tools_error = struct
8394
(* Could not find the module in the environment *)
8495
| `Parent of parent_lookup_error ]
8596

97+
and simple_constructor_lookup_error =
98+
[ `LocalConstructor of
99+
Env.t * Ident.constructor
100+
(* Internal error: Found local path during lookup *)
101+
| `Find_failure
102+
(* Internal error: the type was not found in the parent signature *)
103+
| `Lookup_failureC of
104+
Identifier.Path.Constructor.t
105+
(* Could not find the module in the environment *)
106+
| `ParentC of simple_datatype_lookup_error ]
107+
86108
and parent_lookup_error =
87109
[ `Parent_sig of
88110
expansion_of_module_error
@@ -110,6 +132,8 @@ module Tools_error = struct
110132
type any =
111133
[ simple_type_lookup_error
112134
| simple_value_lookup_error
135+
| simple_constructor_lookup_error
136+
| simple_datatype_lookup_error
113137
| simple_module_type_lookup_error
114138
| simple_module_type_expr_of_module_error
115139
| simple_module_lookup_error
@@ -147,6 +171,10 @@ module Tools_error = struct
147171
| `LocalMT (_, id) -> Format.fprintf fmt "Local id found: %a" Ident.fmt id
148172
| `Local (_, id) -> Format.fprintf fmt "Local id found: %a" Ident.fmt id
149173
| `LocalType (_, id) -> Format.fprintf fmt "Local id found: %a" Ident.fmt id
174+
| `LocalDataType (_, id) ->
175+
Format.fprintf fmt "Local id found: %a" Ident.fmt id
176+
| `LocalConstructor (_, id) ->
177+
Format.fprintf fmt "Local id found: %a" Ident.fmt id
150178
| `LocalValue (_, id) ->
151179
Format.fprintf fmt "Local id found: %a" Ident.fmt id
152180
| `Find_failure -> Format.fprintf fmt "Find failure"
@@ -168,9 +196,14 @@ module Tools_error = struct
168196
Format.fprintf fmt "Lookup failure (value): %a"
169197
Component.Fmt.model_identifier
170198
(m :> Odoc_model.Paths.Identifier.t)
199+
| `Lookup_failureC m ->
200+
Format.fprintf fmt "Lookup failure (value): %a"
201+
Component.Fmt.model_identifier
202+
(m :> Odoc_model.Paths.Identifier.t)
171203
| `ApplyNotFunctor -> Format.fprintf fmt "Apply module is not a functor"
172204
| `Class_replaced -> Format.fprintf fmt "Class replaced"
173205
| `Parent p -> pp fmt (p :> any)
206+
| `ParentC p -> pp fmt (p :> any)
174207
| `UnexpandedTypeOf t ->
175208
Format.fprintf fmt "Unexpanded `module type of` expression: %a"
176209
Component.Fmt.module_type_type_of_desc t
@@ -206,7 +239,9 @@ let is_unexpanded_module_type_of =
206239
| `Find_failure -> false
207240
| `Lookup_failure _ -> false
208241
| `Lookup_failure_root _ -> false
242+
| `Lookup_failureC _ -> false
209243
| `Parent p -> inner (p :> any)
244+
| `ParentC p -> inner (p :> any)
210245
| `Parent_sig p -> inner (p :> any)
211246
| `Parent_module_type p -> inner (p :> any)
212247
| `Parent_expr p -> inner (p :> any)
@@ -224,6 +259,8 @@ let is_unexpanded_module_type_of =
224259
| `Lookup_failureT _ -> false
225260
| `Lookup_failureV _ -> false
226261
| `LocalType _ -> false
262+
| `LocalDataType _ -> false
263+
| `LocalConstructor _ -> false
227264
| `LocalValue _ -> false
228265
| `Class_replaced -> false
229266
| `OpaqueClass -> false
@@ -298,6 +335,7 @@ type what =
298335
| `Module of Identifier.Module.t
299336
| `Module_type of Identifier.Signature.t
300337
| `Module_path of Cpath.module_
338+
| `Constructor_path of Cpath.constructor
301339
| `Module_type_path of Cpath.module_type
302340
| `Module_type_U of Component.ModuleType.U.expr
303341
| `Include of Component.Include.decl
@@ -350,6 +388,7 @@ let report ~(what : what) ?tools_error action =
350388
| `Type cfrag -> r "type" type_fragment cfrag
351389
| `Type_path path -> r "type" type_path path
352390
| `Value_path path -> r "value" value_path path
391+
| `Constructor_path path -> r "constructor" constructor_path path
353392
| `Class_type_path path -> r "class_type" class_type_path path
354393
| `With_module frag -> r "module substitution" module_fragment frag
355394
| `With_module_type frag ->

src/xref2/find.ml

Lines changed: 24 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -111,6 +111,12 @@ let type_in_sig sg name =
111111
Some (`FClassType (N.class_type' id, c))
112112
| _ -> None)
113113

114+
let datatype_in_sig sg name =
115+
find_in_sig sg (function
116+
| Signature.Type (id, _, m) when N.type_ id = name ->
117+
Some (`FType (N.type' id, Delayed.get m))
118+
| _ -> None)
119+
114120
type removed_type =
115121
[ `FType_removed of TypeName.t * TypeExpr.t * TypeDecl.Equation.t ]
116122

@@ -121,6 +127,8 @@ type careful_module_type =
121127

122128
type careful_type = [ type_ | removed_type ]
123129

130+
type careful_datatype = [ datatype | removed_type ]
131+
124132
type careful_class = [ class_ | removed_type ]
125133

126134
let careful_module_in_sig sg name =
@@ -156,11 +164,10 @@ let careful_type_in_sig sg name =
156164
| Some _ as x -> x
157165
| None -> removed_type_in_sig sg name
158166

159-
let datatype_in_sig sg name =
160-
find_in_sig sg (function
161-
| Signature.Type (id, _, t) when N.type_ id = name ->
162-
Some (`FType (N.type' id, Component.Delayed.get t))
163-
| _ -> None)
167+
let careful_datatype_in_sig sg name =
168+
match datatype_in_sig sg name with
169+
| Some _ as x -> x
170+
| None -> removed_type_in_sig sg name
164171

165172
let class_in_sig sg name =
166173
filter_in_sig sg (function
@@ -177,6 +184,18 @@ let careful_class_in_sig sg name =
177184
| Some _ as x -> x
178185
| None -> removed_type_in_sig sg name
179186

187+
let constructor_in_type (typ : TypeDecl.t) name =
188+
let rec find_cons = function
189+
| ({ TypeDecl.Constructor.name = name'; _ } as cons) :: _ when name' = name
190+
->
191+
Some (`FConstructor cons)
192+
| _ :: tl -> find_cons tl
193+
| [] -> None
194+
in
195+
match typ.representation with
196+
| Some (Variant cons) -> find_cons cons
197+
| Some (Record _) | Some Extensible | None -> None
198+
180199
let any_in_type (typ : TypeDecl.t) name =
181200
let rec find_cons = function
182201
| ({ TypeDecl.Constructor.name = name'; _ } as cons) :: _ when name' = name

src/xref2/find.mli

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -71,6 +71,8 @@ val extension_in_sig : Signature.t -> string -> extension option
7171

7272
val any_in_type : TypeDecl.t -> string -> any_in_type option
7373

74+
val constructor_in_type : TypeDecl.t -> string -> constructor option
75+
7476
val any_in_typext : Extension.t -> string -> extension option
7577

7678
val method_in_class_signature : ClassSignature.t -> string -> method_ option
@@ -114,6 +116,8 @@ type careful_module_type =
114116

115117
type careful_type = [ type_ | removed_type ]
116118

119+
type careful_datatype = [ datatype | removed_type ]
120+
117121
type careful_class = [ class_ | removed_type ]
118122

119123
val careful_module_in_sig : Signature.t -> string -> careful_module option
@@ -123,4 +127,6 @@ val careful_module_type_in_sig :
123127

124128
val careful_type_in_sig : Signature.t -> string -> careful_type option
125129

130+
val careful_datatype_in_sig : Signature.t -> string -> careful_datatype option
131+
126132
val careful_class_in_sig : Signature.t -> string -> careful_class option

src/xref2/link.ml

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,8 @@ let rec should_reresolve : Paths.Path.Resolved.t -> bool =
106106
should_reresolve (x :> t) || should_resolve (y :> Paths.Path.t)
107107
| `CanonicalType (x, y) ->
108108
should_reresolve (x :> t) || should_resolve (y :> Paths.Path.t)
109+
| `CanonicalDataType (x, y) ->
110+
should_reresolve (x :> t) || should_resolve (y :> Paths.Path.t)
109111
| `Apply (x, y) ->
110112
should_reresolve (x :> t) || should_reresolve (y :> Paths.Path.Resolved.t)
111113
| `SubstT (x, y) -> should_reresolve (x :> t) || should_reresolve (y :> t)
@@ -120,12 +122,19 @@ let rec should_reresolve : Paths.Path.Resolved.t -> bool =
120122
| `ModuleType (p, _)
121123
| `Module (p, _) ->
122124
should_reresolve (p :> t)
125+
| `Constructor (p, _) -> should_reresolve (p :> t)
123126
| `OpaqueModule m -> should_reresolve (m :> t)
124127
| `OpaqueModuleType m -> should_reresolve (m :> t)
125128

126129
and should_resolve : Paths.Path.t -> bool =
127130
fun p -> match p with `Resolved p -> should_reresolve p | _ -> true
128131

132+
and should_resolve_constructor : Paths.Path.Constructor.t -> bool =
133+
fun p ->
134+
match p with
135+
| `Resolved p -> should_reresolve (p :> Paths.Path.Resolved.t)
136+
| _ -> true
137+
129138
let type_path : Env.t -> Paths.Path.Type.t -> Paths.Path.Type.t =
130139
fun env p ->
131140
if not (should_resolve (p :> Paths.Path.t)) then p
@@ -162,6 +171,25 @@ let value_path : Env.t -> Paths.Path.Value.t -> Paths.Path.Value.t =
162171
Errors.report ~what:(`Value_path cp) ~tools_error:e `Lookup;
163172
p)
164173

174+
let constructor_path :
175+
Env.t -> Paths.Path.Constructor.t -> Paths.Path.Constructor.t =
176+
fun env p ->
177+
if not (should_resolve_constructor p) then p
178+
else
179+
let cp = Component.Of_Lang.(constructor_path (empty ()) p) in
180+
match cp with
181+
| `Resolved p ->
182+
let result = Tools.reresolve_constructor env p in
183+
`Resolved Lang_of.(Path.resolved_constructor (empty ()) result)
184+
| _ -> (
185+
match Tools.resolve_constructor_path env cp with
186+
| Ok p' ->
187+
let result = Tools.reresolve_constructor env p' in
188+
`Resolved Lang_of.(Path.resolved_constructor (empty ()) result)
189+
| Error e ->
190+
Errors.report ~what:(`Constructor_path cp) ~tools_error:e `Lookup;
191+
p)
192+
165193
let class_type_path : Env.t -> Paths.Path.ClassType.t -> Paths.Path.ClassType.t
166194
=
167195
fun env p ->

0 commit comments

Comments
 (0)