Skip to content

Commit c00a46e

Browse files
committed
more precise extension mismatch error messages
1 parent 2452b86 commit c00a46e

File tree

11 files changed

+129
-117
lines changed

11 files changed

+129
-117
lines changed

boot/ocamlc

2.48 KB
Binary file not shown.

boot/ocamllex

244 Bytes
Binary file not shown.

testsuite/tests/shadow_include/shadow_all.ml

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -100,11 +100,11 @@ end
100100
Line 4, characters 2-11:
101101
include S
102102
^^^^^^^^^
103-
Error: Illegal shadowing of included type t/1155 by t/1172
103+
Error: Illegal shadowing of included type t/1143 by t/1160
104104
Line 2, characters 2-11:
105-
Type t/1155 came from this include
105+
Type t/1143 came from this include
106106
Line 3, characters 2-24:
107-
The value ignore has no valid type if t/1155 is shadowed
107+
The value ignore has no valid type if t/1143 is shadowed
108108
|}]
109109

110110
module type Module = sig
@@ -140,11 +140,11 @@ end
140140
Line 4, characters 2-11:
141141
include S
142142
^^^^^^^^^
143-
Error: Illegal shadowing of included module M/1247 by M/1264
143+
Error: Illegal shadowing of included module M/1231 by M/1248
144144
Line 2, characters 2-11:
145-
Module M/1247 came from this include
145+
Module M/1231 came from this include
146146
Line 3, characters 2-26:
147-
The value ignore has no valid type if M/1247 is shadowed
147+
The value ignore has no valid type if M/1231 is shadowed
148148
|}]
149149

150150

@@ -181,11 +181,11 @@ end
181181
Line 4, characters 2-11:
182182
include S
183183
^^^^^^^^^
184-
Error: Illegal shadowing of included module type T/1336 by T/1354
184+
Error: Illegal shadowing of included module type T/1316 by T/1334
185185
Line 2, characters 2-11:
186-
Module type T/1336 came from this include
186+
Module type T/1316 came from this include
187187
Line 3, characters 2-39:
188-
The module F has no valid type if T/1336 is shadowed
188+
The module F has no valid type if T/1316 is shadowed
189189
|}]
190190

191191
module type Extension = sig
@@ -198,11 +198,11 @@ end
198198
Line 4, characters 2-11:
199199
include S
200200
^^^^^^^^^
201-
Error: Illegal shadowing of included type ext/1372 by ext/1389
201+
Error: Illegal shadowing of included type ext/1352 by ext/1369
202202
Line 2, characters 2-11:
203-
Type ext/1372 came from this include
203+
Type ext/1352 came from this include
204204
Line 3, characters 14-16:
205-
The extension constructor C2 has no valid type if ext/1372 is shadowed
205+
The extension constructor C2 has no valid type if ext/1352 is shadowed
206206
|}]
207207

208208
module type Class = sig

testsuite/tests/typing-modules/Test.ml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -141,6 +141,7 @@ Error: Signature mismatch:
141141
type t += E of int
142142
is not included in
143143
type t += E
144+
The arities for field E differ.
144145
|}];;
145146

146147
module M : sig type t += E of char end = struct type t += E of int end;;
@@ -157,6 +158,7 @@ Error: Signature mismatch:
157158
type t += E of int
158159
is not included in
159160
type t += E of char
161+
The types for field E are not equal.
160162
|}];;
161163

162164
module M : sig type t += C of int end = struct type t += E of int end;;
@@ -191,4 +193,5 @@ Error: Signature mismatch:
191193
type t += E of int
192194
is not included in
193195
type t += E of { x : int; }
196+
The types for field E are not equal.
194197
|}];;

typing/includecore.ml

Lines changed: 60 additions & 61 deletions
Original file line numberDiff line numberDiff line change
@@ -169,34 +169,32 @@ let report_type_mismatch0 first second decl ppf err =
169169
"uses unboxed representation"
170170
| Immediate -> pr "%s is not an immediate type" first
171171

172-
let report_type_mismatch first second decl ppf =
173-
List.iter
174-
(fun err ->
175-
if err = Manifest then () else
176-
Format.fprintf ppf "@ %a." (report_type_mismatch0 first second decl) err)
172+
let report_type_mismatch first second decl ppf err =
173+
if err = Manifest then () else
174+
Format.fprintf ppf "@ %a." (report_type_mismatch0 first second decl) err
177175

178176
let rec compare_constructor_arguments ~loc env cstr params1 params2 arg1 arg2 =
179177
match arg1, arg2 with
180178
| Types.Cstr_tuple arg1, Types.Cstr_tuple arg2 ->
181-
if List.length arg1 <> List.length arg2 then [Field_arity cstr]
179+
if List.length arg1 <> List.length arg2 then Some (Field_arity cstr)
182180
else if
183181
(* Ctype.equal must be called on all arguments at once, cf. PR#7378 *)
184182
Ctype.equal env true (params1 @ arg1) (params2 @ arg2)
185-
then [] else [Field_type cstr]
183+
then None else Some (Field_type cstr)
186184
| Types.Cstr_record l1, Types.Cstr_record l2 ->
187185
compare_records env ~loc params1 params2 0 l1 l2
188-
| _ -> [Field_type cstr]
186+
| _ -> Some (Field_type cstr)
189187

190188
and compare_variants ~loc env params1 params2 n
191189
(cstrs1 : Types.constructor_declaration list)
192190
(cstrs2 : Types.constructor_declaration list) =
193191
match cstrs1, cstrs2 with
194-
[], [] -> []
195-
| [], c::_ -> [Field_missing (true, c.Types.cd_id)]
196-
| c::_, [] -> [Field_missing (false, c.Types.cd_id)]
192+
[], [] -> None
193+
| [], c::_ -> Some (Field_missing (true, c.Types.cd_id))
194+
| c::_, [] -> Some (Field_missing (false, c.Types.cd_id))
197195
| cd1::rem1, cd2::rem2 ->
198196
if Ident.name cd1.cd_id <> Ident.name cd2.cd_id then
199-
[Field_names (n, cd1.cd_id, cd2.cd_id)]
197+
Some (Field_names (n, cd1.cd_id, cd2.cd_id))
200198
else begin
201199
Builtin_attributes.check_deprecated_inclusion
202200
~def:cd1.cd_loc
@@ -210,14 +208,14 @@ and compare_variants ~loc env params1 params2 n
210208
if Ctype.equal env true [r1] [r2] then
211209
compare_constructor_arguments ~loc env cd1.cd_id [r1] [r2]
212210
cd1.cd_args cd2.cd_args
213-
else [Field_type cd1.cd_id]
211+
else Some (Field_type cd1.cd_id)
214212
| Some _, None | None, Some _ ->
215-
[Field_type cd1.cd_id]
213+
Some (Field_type cd1.cd_id)
216214
| _ ->
217215
compare_constructor_arguments ~loc env cd1.cd_id
218216
params1 params2 cd1.cd_args cd2.cd_args
219217
in
220-
if r <> [] then r
218+
if r <> None then r
221219
else compare_variants ~loc env params1 params2 (n+1) rem1 rem2
222220
end
223221

@@ -226,14 +224,14 @@ and compare_records ~loc env params1 params2 n
226224
(labels1 : Types.label_declaration list)
227225
(labels2 : Types.label_declaration list) =
228226
match labels1, labels2 with
229-
[], [] -> []
230-
| [], l::_ -> [Field_missing (true, l.Types.ld_id)]
231-
| l::_, [] -> [Field_missing (false, l.Types.ld_id)]
227+
[], [] -> None
228+
| [], l::_ -> Some (Field_missing (true, l.Types.ld_id))
229+
| l::_, [] -> Some (Field_missing (false, l.Types.ld_id))
232230
| ld1::rem1, ld2::rem2 ->
233231
if Ident.name ld1.ld_id <> Ident.name ld2.ld_id
234-
then [Field_names (n, ld1.ld_id, ld2.ld_id)]
232+
then Some (Field_names (n, ld1.ld_id, ld2.ld_id))
235233
else if ld1.ld_mutable <> ld2.ld_mutable then
236-
[Field_mutable ld1.ld_id]
234+
Some (Field_mutable ld1.ld_id)
237235
else begin
238236
Builtin_attributes.check_deprecated_mutable_inclusion
239237
~def:ld1.ld_loc
@@ -248,7 +246,7 @@ and compare_records ~loc env params1 params2 n
248246
(n+1)
249247
rem1 rem2
250248
else
251-
[Field_type ld1.ld_id]
249+
Some (Field_type ld1.ld_id)
252250
end
253251

254252
let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
@@ -258,37 +256,37 @@ let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
258256
loc
259257
decl1.type_attributes decl2.type_attributes
260258
name;
261-
if decl1.type_arity <> decl2.type_arity then [Arity] else
262-
if not (private_flags decl1 decl2) then [Privacy] else
259+
if decl1.type_arity <> decl2.type_arity then Some Arity else
260+
if not (private_flags decl1 decl2) then Some Privacy else
263261
let err = match (decl1.type_manifest, decl2.type_manifest) with
264262
(_, None) ->
265263
if Ctype.equal env true decl1.type_params decl2.type_params
266-
then [] else [Constraint]
264+
then None else Some Constraint
267265
| (Some ty1, Some ty2) ->
268266
if type_manifest env ty1 decl1.type_params ty2 decl2.type_params
269267
decl2.type_private
270-
then [] else [Manifest]
268+
then None else Some Manifest
271269
| (None, Some ty2) ->
272270
let ty1 =
273271
Btype.newgenty (Tconstr(Pident id, decl2.type_params, ref Mnil))
274272
in
275273
if Ctype.equal env true decl1.type_params decl2.type_params then
276-
if Ctype.equal env false [ty1] [ty2] then []
277-
else [Manifest]
278-
else [Constraint]
274+
if Ctype.equal env false [ty1] [ty2] then None
275+
else Some Manifest
276+
else Some Constraint
279277
in
280-
if err <> [] then err else
278+
if err <> None then err else
281279
let err =
282280
match (decl2.type_kind, decl1.type_unboxed.unboxed,
283281
decl2.type_unboxed.unboxed) with
284-
| Type_abstract, _, _ -> []
285-
| _, true, false -> [Unboxed_representation false]
286-
| _, false, true -> [Unboxed_representation true]
287-
| _ -> []
282+
| Type_abstract, _, _ -> None
283+
| _, true, false -> Some (Unboxed_representation false)
284+
| _, false, true -> Some (Unboxed_representation true)
285+
| _ -> None
288286
in
289-
if err <> [] then err else
287+
if err <> None then err else
290288
let err = match (decl1.type_kind, decl2.type_kind) with
291-
(_, Type_abstract) -> []
289+
(_, Type_abstract) -> None
292290
| (Type_variant cstrs1, Type_variant cstrs2) ->
293291
if mark then begin
294292
let mark cstrs usage name decl =
@@ -312,26 +310,26 @@ let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
312310
compare_records ~loc env decl1.type_params
313311
decl2.type_params 1 labels1 labels2
314312
in
315-
if err <> [] || rep1 = rep2 then err else
316-
[Record_representation (rep2 = Record_float)]
317-
| (Type_open, Type_open) -> []
318-
| (_, _) -> [Kind]
313+
if err <> None || rep1 = rep2 then err else
314+
Some (Record_representation (rep2 = Record_float))
315+
| (Type_open, Type_open) -> None
316+
| (_, _) -> Some Kind
319317
in
320-
if err <> [] then err else
318+
if err <> None then err else
321319
let abstr = decl2.type_kind = Type_abstract && decl2.type_manifest = None in
322320
(* If attempt to assign a non-immediate type (e.g. string) to a type that
323321
* must be immediate, then we error *)
324322
let err =
325323
if abstr &&
326324
not decl1.type_immediate &&
327325
decl2.type_immediate then
328-
[Immediate]
329-
else []
326+
Some Immediate
327+
else None
330328
in
331-
if err <> [] then err else
329+
if err <> None then err else
332330
let need_variance =
333331
abstr || decl1.type_private = Private || decl1.type_kind = Type_open in
334-
if not need_variance then [] else
332+
if not need_variance then None else
335333
let abstr = abstr || decl2.type_private = Private in
336334
let opn = decl2.type_kind = Type_open && decl2.type_manifest = None in
337335
let constrained ty = not (Btype.(is_Tvar (repr ty))) in
@@ -346,7 +344,7 @@ let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
346344
let (p1,n1,i1,j1) = get_lower v1 and (p2,n2,i2,j2) = get_lower v2 in
347345
imp abstr (imp p2 p1 && imp n2 n1 && imp i2 i1 && imp j2 j1))
348346
decl2.type_params (List.combine decl1.type_variance decl2.type_variance)
349-
then [] else [Variance]
347+
then None else Some Variance
350348

351349
(* Inclusion between extension constructors *)
352350

@@ -364,21 +362,22 @@ let extension_constructors ~loc env ~mark id ext1 ext2 =
364362
let ty2 =
365363
Btype.newgenty (Tconstr(ext2.ext_type_path, ext2.ext_type_params, ref Mnil))
366364
in
367-
if Ctype.equal env true
368-
(ty1 :: ext1.ext_type_params)
369-
(ty2 :: ext2.ext_type_params)
370-
then
371-
if compare_constructor_arguments ~loc env (Ident.create "")
365+
if not (Ctype.equal env true (ty1 :: ext1.ext_type_params)
366+
(ty2 :: ext2.ext_type_params))
367+
then Some (Field_type id)
368+
else
369+
let r =
370+
compare_constructor_arguments ~loc env id
372371
ext1.ext_type_params ext2.ext_type_params
373-
ext1.ext_args ext2.ext_args = [] then
374-
if match ext1.ext_ret_type, ext2.ext_ret_type with
375-
Some r1, Some r2 when not (Ctype.equal env true [r1] [r2]) -> false
376-
| Some _, None | None, Some _ -> false
377-
| _ -> true
378-
then
372+
ext1.ext_args ext2.ext_args
373+
in
374+
if r <> None then r else
375+
match ext1.ext_ret_type, ext2.ext_ret_type with
376+
Some r1, Some r2 when not (Ctype.equal env true [r1] [r2]) ->
377+
Some (Field_type id)
378+
| Some _, None | None, Some _ ->
379+
Some (Field_type id)
380+
| _ ->
379381
match ext1.ext_private, ext2.ext_private with
380-
Private, Public -> false
381-
| _, _ -> true
382-
else false
383-
else false
384-
else false
382+
Private, Public -> Some Privacy
383+
| _, _ -> None

typing/includecore.mli

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -44,15 +44,15 @@ val type_declarations:
4444
?equality:bool ->
4545
loc:Location.t ->
4646
Env.t -> mark:bool -> string ->
47-
type_declaration -> Ident.t -> type_declaration -> type_mismatch list
47+
type_declaration -> Ident.t -> type_declaration -> type_mismatch option
4848

4949
val extension_constructors:
5050
loc:Location.t -> Env.t -> mark:bool -> Ident.t ->
51-
extension_constructor -> extension_constructor -> bool
51+
extension_constructor -> extension_constructor -> type_mismatch option
5252
(*
5353
val class_types:
5454
Env.t -> class_type -> class_type -> bool
5555
*)
5656

5757
val report_type_mismatch:
58-
string -> string -> string -> Format.formatter -> type_mismatch list -> unit
58+
string -> string -> string -> Format.formatter -> type_mismatch -> unit

0 commit comments

Comments
 (0)