Skip to content

Commit

Permalink
Stdlib injectivity: update tests.
Browse files Browse the repository at this point in the history
  • Loading branch information
yallop committed Jul 18, 2020
1 parent 2c87261 commit 9780cc4
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 8 deletions.
13 changes: 6 additions & 7 deletions testsuite/tests/typing-gadts/pr5985.ml
Expand Up @@ -70,16 +70,15 @@ Error: In this definition, a type variable cannot be deduced
(* It is not OK to allow modules exported by other compilation units *)
type (_,_) eq = Eq : ('a,'a) eq;;
let eq = Obj.magic Eq;;
(* pretend that Queue.t is not injective *)
let eq : ('a Queue.t, 'b Queue.t) eq = eq;;
type _ t = T : 'a -> 'a Queue.t t;; (* fail *)
let eq : (('a, 'b) Ephemeron.K1.t, ('c, 'd) Ephemeron.K1.t) eq = eq;;
type _ t = T : 'a -> ('a, 'b) Ephemeron.K1.t t;; (* fail *)
[%%expect{|
type (_, _) eq = Eq : ('a, 'a) eq
val eq : 'a = <poly>
val eq : ('a Queue.t, 'b Queue.t) eq = Eq
Line 5, characters 0-33:
5 | type _ t = T : 'a -> 'a Queue.t t;; (* fail *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
val eq : (('a, 'b) Ephemeron.K1.t, ('c, 'd) Ephemeron.K1.t) eq = Eq
Line 4, characters 0-46:
4 | type _ t = T : 'a -> ('a, 'b) Ephemeron.K1.t t;; (* fail *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: In this definition, a type variable cannot be deduced
from the type parameters.
|}];;
Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/typing-implicit_unpack/implicit_unpack.ml
Expand Up @@ -303,7 +303,7 @@ end
module type MapT =
sig
type key
type +'a t
type +!'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
Expand Down

0 comments on commit 9780cc4

Please sign in to comment.