Skip to content

Commit

Permalink
Use the structured errors from ocaml#10170 for better error messages
Browse files Browse the repository at this point in the history
  • Loading branch information
Antal Spector-Zabusky authored and antalsz committed May 4, 2021
1 parent c26570e commit 056dddd
Show file tree
Hide file tree
Showing 28 changed files with 204 additions and 178 deletions.
5 changes: 5 additions & 0 deletions .depend
Expand Up @@ -638,16 +638,19 @@ typing/envaux.cmi : \
typing/errortrace.cmo : \
typing/types.cmi \
typing/path.cmi \
typing/env.cmi \
parsing/asttypes.cmi \
typing/errortrace.cmi
typing/errortrace.cmx : \
typing/types.cmx \
typing/path.cmx \
typing/env.cmx \
parsing/asttypes.cmi \
typing/errortrace.cmi
typing/errortrace.cmi : \
typing/types.cmi \
typing/path.cmi \
typing/env.cmi \
parsing/asttypes.cmi
typing/ident.cmo : \
utils/misc.cmi \
Expand All @@ -667,13 +670,15 @@ typing/includeclass.cmo : \
typing/types.cmi \
typing/printtyp.cmi \
typing/path.cmi \
typing/errortrace.cmi \
typing/ctype.cmi \
parsing/builtin_attributes.cmi \
typing/includeclass.cmi
typing/includeclass.cmx : \
typing/types.cmx \
typing/printtyp.cmx \
typing/path.cmx \
typing/errortrace.cmx \
typing/ctype.cmx \
parsing/builtin_attributes.cmx \
typing/includeclass.cmi
Expand Down
16 changes: 8 additions & 8 deletions testsuite/tests/typing-extensions/extensions.ml
Expand Up @@ -322,9 +322,9 @@ Error: Signature mismatch:
type ('a, 'b) bar += A of int
Constructors do not match:
A of float
is not compatible with:
is not the same as:
A of int
The types are not equal.
The type float is not equal to the type int
|}]

module M : sig
Expand All @@ -348,9 +348,9 @@ Error: Signature mismatch:
type ('a, 'b) bar += A of 'a
Constructors do not match:
A of 'b
is not compatible with:
is not the same as:
A of 'a
The types are not equal.
The type 'b is not equal to the type 'a
|}]

module M : sig
Expand All @@ -374,9 +374,9 @@ Error: Signature mismatch:
type ('a, 'b) bar = A of 'a
Constructors do not match:
A of 'a
is not compatible with:
is not the same as:
A of 'a
The types are not equal.
The type 'a is not equal to the type 'b
|}];;


Expand All @@ -401,9 +401,9 @@ Error: Signature mismatch:
type ('a, 'b) bar += A : 'c -> ('c, 'd) bar
Constructors do not match:
A : 'd -> ('c, 'd) bar
is not compatible with:
is not the same as:
A : 'c -> ('c, 'd) bar
The types are not equal.
The type 'd is not equal to the type 'c
|}]

(* Extensions can be rebound *)
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/typing-gadts/pr7160.ml
Expand Up @@ -20,7 +20,7 @@ Lines 4-5, characters 0-77:
Error: This variant or record definition does not match that of type 'a t
Constructors do not match:
Same : 'l t -> 'l t
is not compatible with:
is not the same as:
Same : 'l1 t -> 'l2 t
The types are not equal.
The type 'l is not equal to the type 'l1
|}];;
4 changes: 2 additions & 2 deletions testsuite/tests/typing-gadts/pr7378.ml
Expand Up @@ -21,9 +21,9 @@ Lines 2-3, characters 2-37:
Error: This variant or record definition does not match that of type X.t
Constructors do not match:
A : 'a * 'b * ('a -> unit) -> X.t
is not compatible with:
is not the same as:
A : 'a * 'b * ('b -> unit) -> X.t
The types are not equal.
The type 'a is not equal to the type 'b
|}]

(* would segfault
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/typing-misc/enrich_typedecl.ml
Expand Up @@ -254,7 +254,7 @@ Error: Signature mismatch:
type ('a, 'b) t = Foo of 'a
Constructors do not match:
Foo of 'b
is not compatible with:
is not the same as:
Foo of 'a
The types are not equal.
The type 'b is not equal to the type 'a
|}];;
2 changes: 1 addition & 1 deletion testsuite/tests/typing-misc/includeclass_errors.ml
Expand Up @@ -107,7 +107,7 @@ Error: Signature mismatch:
class ['a] c : object end
does not match
class ['a] c : object constraint 'a = int end
A type parameter has type 'a but is expected to have type int
A type parameter has type 'a0 but is expected to have type int
|}]

module M: sig
Expand Down
11 changes: 5 additions & 6 deletions testsuite/tests/typing-misc/pr6416.ml
Expand Up @@ -52,9 +52,9 @@ Error: Signature mismatch:
type u = A of t/2
Constructors do not match:
A of t/1
is not compatible with:
is not the same as:
A of t/2
The types are not equal.
The type t/1 is not equal to the type t/2
Line 4, characters 9-19:
Definition of type t/1
Line 2, characters 2-11:
Expand Down Expand Up @@ -121,9 +121,9 @@ Error: Signature mismatch:
type t = A of T/2.t
Constructors do not match:
A of T/1.t
is not compatible with:
is not the same as:
A of T/2.t
The types are not equal.
The type T/1.t is not equal to the type T/2.t
Line 5, characters 6-34:
Definition of module T/1
Line 2, characters 2-30:
Expand Down Expand Up @@ -308,8 +308,7 @@ Error: Signature mismatch:
class type c = object method m : t/2 end
does not match
class type c = object method m : t/1 end
The method m has type t/2 but is expected to have type t/1
Type t/2 is not equal to type t/1 = K.t
The method m has type t/2 but is expected to have type t/1 = K.t
Line 12, characters 4-10:
Definition of type t/1
Line 9, characters 2-8:
Expand Down
6 changes: 3 additions & 3 deletions testsuite/tests/typing-misc/records.ml
Expand Up @@ -221,7 +221,7 @@ Line 2, characters 0-37:
Error: This variant or record definition does not match that of type d
Fields do not match:
y : int;
is not compatible with:
is not the same as:
mutable y : int;
This is mutable and the original is not.
|}]
Expand All @@ -243,9 +243,9 @@ Line 1, characters 0-31:
Error: This variant or record definition does not match that of type d
Fields do not match:
x : int;
is not compatible with:
is not the same as:
x : float;
The types are not equal.
The type int is not equal to the type float
|}]

type unboxed = d = {x:float} [@@unboxed]
Expand Down
6 changes: 3 additions & 3 deletions testsuite/tests/typing-misc/variant.ml
Expand Up @@ -98,9 +98,9 @@ Line 1, characters 0-32:
Error: This variant or record definition does not match that of type d
Constructors do not match:
X of int
is not compatible with:
is not the same as:
X of float
The types are not equal.
The type int is not equal to the type float
|}]

type unboxed = d = X of float [@@unboxed]
Expand Down Expand Up @@ -143,7 +143,7 @@ Error: Signature mismatch:
type t = Foo of int
Constructors do not match:
Foo : int -> t
is not compatible with:
is not the same as:
Foo of int
The first has explicit return type and the second doesn't.
|}]
12 changes: 6 additions & 6 deletions testsuite/tests/typing-modules/Test.ml
Expand Up @@ -97,9 +97,9 @@ Line 3, characters 23-33:
Error: This variant or record definition does not match that of type u
Constructors do not match:
X of bool
is not compatible with:
is not the same as:
X of int
The types are not equal.
The type bool is not equal to the type int
|}];;

(* PR#5815 *)
Expand Down Expand Up @@ -147,7 +147,7 @@ Error: Signature mismatch:
type t += E
Constructors do not match:
E of int
is not compatible with:
is not the same as:
E
They have different arities.
|}];;
Expand All @@ -168,9 +168,9 @@ Error: Signature mismatch:
type t += E of char
Constructors do not match:
E of int
is not compatible with:
is not the same as:
E of char
The types are not equal.
The type int is not equal to the type char
|}];;

module M : sig type t += C of int end = struct type t += E of int end;;
Expand Down Expand Up @@ -207,7 +207,7 @@ Error: Signature mismatch:
type t += E of { x : int; }
Constructors do not match:
E of int
is not compatible with:
is not the same as:
E of { x : int; }
The second uses inline records and the first doesn't.
|}];;
Expand Up @@ -21,7 +21,7 @@ Error: Signature mismatch:
type t += F
Constructors do not match:
F of int
is not compatible with:
is not the same as:
F
They have different arities.
|}];;
Expand Down
10 changes: 4 additions & 6 deletions testsuite/tests/typing-modules/functors.ml
Expand Up @@ -1617,11 +1617,9 @@ Error: The functor application is ill-typed.
type t = Y of X.t
Constructors do not match:
Y of int
is not compatible with:
is not the same as:
Y of X.t
The types are not equal.
Line 5, characters 0-32:
Definition of module X/1
The type int is not equal to the type X.t
4. Modules do not match:
Z : sig type t = Z.t = Z of int end
is not included in
Expand All @@ -1632,9 +1630,9 @@ Error: The functor application is ill-typed.
type t = Z of X.t
Constructors do not match:
Z of int
is not compatible with:
is not the same as:
Z of X.t
The types are not equal.
The type int is not equal to the type X.t
|}]

(** Final state in the presence of extensions
Expand Down
10 changes: 6 additions & 4 deletions testsuite/tests/typing-modules/inclusion_errors.ml
Expand Up @@ -138,9 +138,9 @@ Error: Signature mismatch:
type t = Foo of int * float
Constructors do not match:
Foo of (int * int) * float
is not compatible with:
is not the same as:
Foo of int * float
The types are not equal.
The type int * int is not equal to the type int
|}];;

module M : sig
Expand Down Expand Up @@ -251,9 +251,11 @@ Error: Signature mismatch:
type t = Foo of [ `Bar of string | `Foo of string ]
Constructors do not match:
Foo of [ `Bar of string ]
is not compatible with:
is not the same as:
Foo of [ `Bar of string | `Foo of string ]
The types are not equal.
The type [ `Bar of string ] is not equal to the type
[ `Bar of string | `Foo of string ]
The first variant type does not allow tag(s) `Foo
|}];;

module M : sig
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/typing-modules/module_type_substitution.ml
Expand Up @@ -149,9 +149,9 @@ Error: In this `with' constraint, the new definition of t
type t = X of int | Y of float
Constructors do not match:
X of x
is not compatible with:
is not the same as:
X of int
The types are not equal.
The type x is not equal to the type int
|}]

(** First class module types require an identity *)
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/typing-modules/pr7818.ml
Expand Up @@ -323,7 +323,7 @@ Line 15, characters 0-69:
Error: This variant or record definition does not match that of type M.t
Constructors do not match:
E of (MkT(M.T).t, MkT(M.T).t) eq
is not compatible with:
is not the same as:
E of (MkT(Desc).t, MkT(Desc).t) eq
The types are not equal.
The type MkT(M.T).t is not equal to the type MkT(Desc).t
|}]
8 changes: 4 additions & 4 deletions testsuite/tests/typing-modules/pr7851.ml
Expand Up @@ -29,9 +29,9 @@ Line 1, characters 0-58:
Error: This variant or record definition does not match that of type M1.t
Constructors do not match:
E of M1.x
is not compatible with:
is not the same as:
E of M1.y
The types are not equal.
The type M1.x is not equal to the type M1.y
|}]

let bool_of_int x =
Expand Down Expand Up @@ -81,7 +81,7 @@ Line 1, characters 0-58:
Error: This variant or record definition does not match that of type M1.t
Constructors do not match:
E of (M1.x, M1.x) eq
is not compatible with:
is not the same as:
E of (M1.x, M1.y) eq
The types are not equal.
The type M1.x is not equal to the type M1.y
|}]
6 changes: 3 additions & 3 deletions testsuite/tests/typing-modules/records_errors_test.ml
Expand Up @@ -42,9 +42,9 @@ Error: Signature mismatch:
}
Fields do not match:
f0 : unit * unit * unit * float * unit * unit * unit;
is not compatible with:
is not the same as:
f0 : unit * unit * unit * int * unit * unit * unit;
The types are not equal.
The type float is not equal to the type int
|}];;


Expand Down Expand Up @@ -88,7 +88,7 @@ Error: Signature mismatch:
}
Fields do not match:
f0 : unit * unit * unit * float * unit * unit * unit;
is not compatible with:
is not the same as:
mutable f0 : unit * unit * unit * int * unit * unit * unit;
The second is mutable and the first is not.
|}];;
Expand Down

0 comments on commit 056dddd

Please sign in to comment.