Skip to content

Commit

Permalink
Add new test cases for failures of type-specific unification methods
Browse files Browse the repository at this point in the history
These test cases will also have improved error messages in the next
non-test commit.  They come from the work done to address reviewer
comments for ocaml#10407.
  • Loading branch information
antalsz committed Jun 17, 2021
1 parent ffcaa5c commit 7483404
Show file tree
Hide file tree
Showing 3 changed files with 154 additions and 0 deletions.
108 changes: 108 additions & 0 deletions testsuite/tests/typing-gadts/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1263,3 +1263,111 @@ Line 7, characters 22-36:
Error: This function should have type int -> int
but its first argument is not labelled
|}]

(* Check got/expected when the order changes *)
module M = struct
type t
end
type (_,_) eq = Refl: ('a,'a) eq
let f (x:M.t) (y: (M.t, int -> int) eq) =
let Refl = y in
if true then fun x -> x + 1 else x
[%%expect{|
module M : sig type t end
type (_, _) eq = Refl : ('a, 'a) eq
Line 7, characters 35-36:
7 | if true then fun x -> x + 1 else x
^
Error: This expression has type M.t = int -> int
but an expression was expected of type int -> int
This instance of int -> int is ambiguous:
it would escape the scope of its equation
|}]

module M = struct
type t
end
type (_,_) eq = Refl: ('a,'a) eq
let f w (x:M.t) (y: (M.t, <m:int>) eq) =
let Refl = y in
let z = if true then x else w in
z#m
[%%expect{|
module M : sig type t end
type (_, _) eq = Refl : ('a, 'a) eq
Line 8, characters 2-3:
8 | z#m
^
Error: This expression has type M.t
It has no method m
Hint: Did you mean m?
|}]

(* Check got/expected when the order changes *)
module M = struct
type t
end
type (_,_) eq = Refl: ('a,'a) eq
let f w (x:M.t) (y: (M.t, <m:int>) eq) =
let Refl = y in
let z = if true then w else x in
z#m
[%%expect{|
module M : sig type t end
type (_, _) eq = Refl : ('a, 'a) eq
Line 8, characters 2-3:
8 | z#m
^
Error: This expression has type M.t
It has no method m
Hint: Did you mean m?
|}]

type (_,_) eq = Refl: ('a,'a) eq
module M = struct
type t = C : (<m:int; ..> as 'a) * ('a, <m:int; b:bool>) eq -> t
end
let f (C (x,y) : M.t) =
let g w =
let Refl = y in
let z = if true then w else x in
z#b
in ()
[%%expect{|
type (_, _) eq = Refl : ('a, 'a) eq
module M :
sig
type t =
C : (< m : int; .. > as 'a) * ('a, < b : bool; m : int >) eq -> t
end
Line 9, characters 4-5:
9 | z#b
^
Error: This expression has type < m : int; .. >
It has no method b
|}]

(* Check got/expected when the order changes *)
type (_,_) eq = Refl: ('a,'a) eq
module M = struct
type t = C : (<m:int; ..> as 'a) * ('a, <m:int; b:bool>) eq -> t
end
let f (C (x,y) : M.t) =
let g w =
let Refl = y in
let z = if true then x else w in
z#b
in ()
[%%expect{|
type (_, _) eq = Refl : ('a, 'a) eq
module M :
sig
type t =
C : (< m : int; .. > as 'a) * ('a, < b : bool; m : int >) eq -> t
end
Line 9, characters 4-5:
9 | z#b
^
Error: This expression has type < m : int; .. >
It has no method b
|}]
28 changes: 28 additions & 0 deletions testsuite/tests/typing-misc/labels.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,34 @@ Error: This function should have type unit -> unit
but its first argument is labelled ?opt
|}];;

(* filter_arrow *)

let (f : x:int -> int) = fun y -> y
[%%expect{|
Line 1, characters 25-35:
1 | let (f : x:int -> int) = fun y -> y
^^^^^^^^^^
Error: This function should have type x:int -> int
but its first argument is not labelled
|}];;

let (f : int -> int) = fun ~y -> y
[%%expect{|
Line 1, characters 23-34:
1 | let (f : int -> int) = fun ~y -> y
^^^^^^^^^^^
Error: This function should have type int -> int
but its first argument is labelled ~y
|}];;

let (f : x:int -> int) = fun ~y -> y
[%%expect{|
Line 1, characters 25-36:
1 | let (f : x:int -> int) = fun ~y -> y
^^^^^^^^^^^
Error: This function should have type x:int -> int
but its first argument is labelled ~y
|}];;

(* More examples *)

Expand Down
18 changes: 18 additions & 0 deletions testsuite/tests/typing-objects/errors.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,3 +34,21 @@ Error: The class type object method x : 'a * float end
The method x has type 'a * float but is expected to have type int
Type 'a * float is not compatible with type int
|}]

let foo = 42#m;;
[%%expect{|
Line 1, characters 10-12:
1 | let foo = 42#m;;
^^
Error: This expression has type int
It has no method m
|}]

let foo = object (self) method foo = self#bar end;;
[%%expect{|
Line 1, characters 37-41:
1 | let foo = object (self) method foo = self#bar end;;
^^^^
Error: This expression has type < foo : 'a >
It has no method bar
|}]

0 comments on commit 7483404

Please sign in to comment.