diff options
author | Richard Eisenberg <eir@seas.upenn.edu> | 2013-08-28 12:05:03 -0400 |
---|---|---|
committer | Richard Eisenberg <eir@cis.upenn.edu> | 2013-09-17 21:41:53 -0400 |
commit | 1e3ca733694f0c9c8cc1d95237eb4b09cee4206f (patch) | |
tree | 73f31ae153ac841d0f8499b5edd98075881bdec4 | |
parent | b4ab30d54540573fbda3f561377d2c5968eb215c (diff) | |
download | haskell-1e3ca733694f0c9c8cc1d95237eb4b09cee4206f.tar.gz |
Update to tests due to change in syntax for role annotations.
70 files changed, 365 insertions, 213 deletions
diff --git a/testsuite/tests/deriving/should_compile/Roles1.hs b/testsuite/tests/deriving/should_compile/Roles1.hs deleted file mode 100644 index d0467c1a90..0000000000 --- a/testsuite/tests/deriving/should_compile/Roles1.hs +++ /dev/null @@ -1,13 +0,0 @@ -{-# LANGUAGE RoleAnnotations, PolyKinds #-} - -module Roles1 where - -data T1 a@N = K1 a -data T2 a@R = K2 a -data T3 (a :: k)@P = K3 -data T4 (a :: * -> *)@N b = K4 (a b) - -data T5 a = K5 a -data T6 a = K6 -data T7 a b = K7 b - diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index bae74bf4dd..d27f829c4a 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -41,9 +41,4 @@ test('T7710', normal, compile, ['']) test('AutoDeriveTypeable', normal, compile, ['']) -test('Roles1', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles2', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles3', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles4', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques']) test('T8138', normal, compile, ['-O2'])
\ No newline at end of file diff --git a/testsuite/tests/deriving/should_fail/Roles11.stderr b/testsuite/tests/deriving/should_fail/Roles11.stderr deleted file mode 100644 index 2b68612999..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles11.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -Roles11.hs:5:1: - Role mismatch on variable a: - Annotation says Representational but role Nominal is required - In the data declaration for ‛T2’ diff --git a/testsuite/tests/deriving/should_fail/Roles5.hs b/testsuite/tests/deriving/should_fail/Roles5.hs deleted file mode 100644 index 8fe983ccb9..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles5.hs +++ /dev/null @@ -1,5 +0,0 @@ -module Roles5 where - -data T a@N -class C a@R -type S a@P = Int
\ No newline at end of file diff --git a/testsuite/tests/deriving/should_fail/Roles5.stderr b/testsuite/tests/deriving/should_fail/Roles5.stderr deleted file mode 100644 index 29018be19d..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles5.stderr +++ /dev/null @@ -1,15 +0,0 @@ - -Roles5.hs:3:8: - Illegal role annotation - Perhaps you intended to use RoleAnnotations - In the data type declaration for ‛T’ - -Roles5.hs:4:9: - Illegal role annotation - Perhaps you intended to use RoleAnnotations - In the declaration for class C - -Roles5.hs:5:8: - Illegal role annotation - Perhaps you intended to use RoleAnnotations - In the declaration for type synonym ‛S’ diff --git a/testsuite/tests/deriving/should_fail/Roles6.hs b/testsuite/tests/deriving/should_fail/Roles6.hs deleted file mode 100644 index 56f80a1e2b..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles6.hs +++ /dev/null @@ -1,5 +0,0 @@ -{-# LANGUAGE RoleAnnotations, TypeFamilies #-} - -module Roles6 where - -type family F a@R diff --git a/testsuite/tests/deriving/should_fail/Roles6.stderr b/testsuite/tests/deriving/should_fail/Roles6.stderr deleted file mode 100644 index 4b89a9e40a..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles6.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -Roles6.hs:5:1: - Illegal role annotation on variable a; - role annotations are not allowed here - In the family declaration for ‛F’ diff --git a/testsuite/tests/deriving/should_fail/Roles7.hs b/testsuite/tests/deriving/should_fail/Roles7.hs deleted file mode 100644 index 5d62803e3a..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles7.hs +++ /dev/null @@ -1,6 +0,0 @@ -{-# LANGUAGE RoleAnnotations #-} - -module Roles7 where - -bar :: Int@P -> Int -bar = id
\ No newline at end of file diff --git a/testsuite/tests/deriving/should_fail/Roles7.stderr b/testsuite/tests/deriving/should_fail/Roles7.stderr deleted file mode 100644 index 5e527a69f7..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles7.stderr +++ /dev/null @@ -1,4 +0,0 @@ - -Roles7.hs:5:8: - Illegal role annotation on Int - In the type signature for ‛bar’ diff --git a/testsuite/tests/deriving/should_fail/Roles8.hs b/testsuite/tests/deriving/should_fail/Roles8.hs deleted file mode 100644 index b05cf5dad4..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles8.hs +++ /dev/null @@ -1,5 +0,0 @@ -{-# LANGUAGE RoleAnnotations, GADTs #-} - -module Roles8 where - -data T1 a@P = K1 a diff --git a/testsuite/tests/deriving/should_fail/Roles8.stderr b/testsuite/tests/deriving/should_fail/Roles8.stderr deleted file mode 100644 index 12aa9fbc78..0000000000 --- a/testsuite/tests/deriving/should_fail/Roles8.stderr +++ /dev/null @@ -1,5 +0,0 @@ - -Roles8.hs:5:1: - Role mismatch on variable a: - Annotation says Phantom but role Representational is required - In the data declaration for ‛T1’ diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index 610f1181fe..607ffa35f7 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -42,16 +42,6 @@ test('T1133A', test('T5863a', normal, compile_fail, ['']) test('T7959', normal, compile_fail, ['']) -test('Roles5', normal, compile_fail, ['']) -test('Roles6', normal, compile_fail, ['']) -test('Roles7', normal, compile_fail, ['']) -test('Roles8', normal, compile_fail, ['']) -test('Roles9', normal, compile_fail, ['']) -test('Roles10', normal, compile_fail, ['']) -test('Roles11', normal, compile_fail, ['']) -test('Roles12', - extra_clean(['Roles12.o-boot', 'Roles12.hi-boot']), - run_command, ['$MAKE --no-print-directory -s Roles12']) test('T1496', normal, compile_fail, ['']) test('T4846', normal, compile_fail, ['']) test('T7148', normal, compile_fail, ['']) diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr index f8e8292313..c77129c13e 100644 --- a/testsuite/tests/indexed-types/should_compile/T3017.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr @@ -4,13 +4,15 @@ TYPE SIGNATURES forall c t t1. (Num t, Num t1, Coll c, Elem c ~ (t, t1)) => c -> c TYPE CONSTRUCTORS Coll :: * -> Constraint - class Coll c@N + class Coll c + Roles: [nominal] RecFlag NonRecursive - type family Elem c@N :: * + type family Elem c :: * empty :: c insert :: Elem c -> c -> c ListColl :: * -> * - data ListColl a@R + data ListColl a No C type associated + Roles: [representational] RecFlag NonRecursive, Promotable = L :: forall a. [a] -> ListColl a Stricts: _ FamilyInstance: none diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr index 1edebd6662..b621614e04 100644 --- a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr @@ -2,24 +2,24 @@ ClosedFam3.hs-boot:5:13: Type constructor ‛Foo’ has conflicting definitions in the module and its hs-boot file - Main module: closed type family Foo a@N :: * where + Main module: closed type family Foo a :: * where Foo Int = Bool Foo Double = Char - Boot file: closed type family Foo a@N :: * where Foo Int = Bool + Boot file: closed type family Foo a :: * where Foo Int = Bool ClosedFam3.hs-boot:8:13: Type constructor ‛Bar’ has conflicting definitions in the module and its hs-boot file - Main module: closed type family Bar a@N :: * where + Main module: closed type family Bar a :: * where Bar Int = Bool Bar Double = Double - Boot file: closed type family Bar a@N :: * where + Boot file: closed type family Bar a :: * where Bar Int = Bool Bar Double = Char ClosedFam3.hs-boot:12:13: Type constructor ‛Baz’ has conflicting definitions in the module and its hs-boot file - Main module: closed type family Baz a@N :: * where Baz Int = Bool - Boot file: closed type family Baz (k::BOX)@N (a::k)@N :: * where + Main module: closed type family Baz a :: * where Baz Int = Bool + Boot file: closed type family Baz (k::BOX) (a::k) :: * where Baz * Int = Bool diff --git a/testsuite/tests/indexed-types/should_fail/Overlap15.hs b/testsuite/tests/indexed-types/should_fail/Overlap15.hs index c150a4028c..2e31b53fbe 100644 --- a/testsuite/tests/indexed-types/should_fail/Overlap15.hs +++ b/testsuite/tests/indexed-types/should_fail/Overlap15.hs @@ -14,3 +14,4 @@ type family F a b c where foo :: Proxy b -> F b [b] Bool foo _ = False + diff --git a/testsuite/tests/polykinds/T7272.hs-boot b/testsuite/tests/polykinds/T7272.hs-boot index 0fcc02f71b..cb349510f8 100644 --- a/testsuite/tests/polykinds/T7272.hs-boot +++ b/testsuite/tests/polykinds/T7272.hs-boot @@ -2,4 +2,5 @@ module T7272 where
-class C (a :: k)@P
+type role C phantom
+class C (a :: k)
diff --git a/testsuite/tests/rename/should_compile/Imp100Aux.hs-boot b/testsuite/tests/rename/should_compile/Imp100Aux.hs-boot index b197c47805..7e1552fb9c 100644 --- a/testsuite/tests/rename/should_compile/Imp100Aux.hs-boot +++ b/testsuite/tests/rename/should_compile/Imp100Aux.hs-boot @@ -1,12 +1,23 @@ {-# LANGUAGE RoleAnnotations #-} module Imp100Aux where -data T1 a@P -data T2 a@P b@P -data T3 a@P b@P c@P -data T4 a@P b@P c@P d@P -data T5 a@P b@P c@P d@P e@P -data T6 a@P -data T7 a@P b@P -data T8 a@P b@P c@P -data T9 a@P b@P c@P d@P -data T10 a@P b@P c@P d@P e@P +data T1 a +data T2 a b +data T3 a b c +data T4 a b c d +data T5 a b c d e +data T6 a +data T7 a b +data T8 a b c +data T9 a b c d +data T10 a b c d e + +type role T1 phantom +type role T2 phantom phantom +type role T3 phantom phantom phantom +type role T4 phantom phantom phantom phantom +type role T5 phantom phantom phantom phantom phantom +type role T6 phantom +type role T7 phantom phantom +type role T8 phantom phantom phantom +type role T9 phantom phantom phantom phantom +type role T10 phantom phantom phantom phantom phantom diff --git a/testsuite/tests/rename/should_compile/Imp10Aux.hs-boot b/testsuite/tests/rename/should_compile/Imp10Aux.hs-boot index cfe980e2f0..f7993110a7 100644 --- a/testsuite/tests/rename/should_compile/Imp10Aux.hs-boot +++ b/testsuite/tests/rename/should_compile/Imp10Aux.hs-boot @@ -1,13 +1,24 @@ {-# LANGUAGE RoleAnnotations #-} module Imp10Aux where -data T1 a@P -data T2 a@P b@P -data T3 a@P b@P c@P -data T4 a@P b@P c@P d@P -data T5 a@P b@P c@P d@P e@P -data T6 a@P -data T7 a@P b@P -data T8 a@P b@P c@P -data T9 a@P b@P c@P d@P -data T10 a@P b@P c@P d@P e@P +data T1 a +data T2 a b +data T3 a b c +data T4 a b c d +data T5 a b c d e +data T6 a +data T7 a b +data T8 a b c +data T9 a b c d +data T10 a b c d e + +type role T1 phantom +type role T2 phantom phantom +type role T3 phantom phantom phantom +type role T4 phantom phantom phantom phantom +type role T5 phantom phantom phantom phantom phantom +type role T6 phantom +type role T7 phantom phantom +type role T8 phantom phantom phantom +type role T9 phantom phantom phantom phantom +type role T10 phantom phantom phantom phantom phantom diff --git a/testsuite/tests/rename/should_compile/Imp500Aux.hs-boot b/testsuite/tests/rename/should_compile/Imp500Aux.hs-boot index 9dc4ea2a74..2798ac0c75 100644 --- a/testsuite/tests/rename/should_compile/Imp500Aux.hs-boot +++ b/testsuite/tests/rename/should_compile/Imp500Aux.hs-boot @@ -1,12 +1,23 @@ {-# LANGUAGE RoleAnnotations #-} module Imp500Aux where -data T1 a@P -data T2 a@P b@P -data T3 a@P b@P c@P -data T4 a@P b@P c@P d@P -data T5 a@P b@P c@P d@P e@P -data T6 a@P -data T7 a@P b@P -data T8 a@P b@P c@P -data T9 a@P b@P c@P d@P -data T10 a@P b@P c@P d@P e@P +data T1 a +data T2 a b +data T3 a b c +data T4 a b c d +data T5 a b c d e +data T6 a +data T7 a b +data T8 a b c +data T9 a b c d +data T10 a b c d e + +type role T1 phantom +type role T2 phantom phantom +type role T3 phantom phantom phantom +type role T4 phantom phantom phantom phantom +type role T5 phantom phantom phantom phantom phantom +type role T6 phantom +type role T7 phantom phantom +type role T8 phantom phantom phantom +type role T9 phantom phantom phantom phantom +type role T10 phantom phantom phantom phantom phantom diff --git a/testsuite/tests/rename/should_fail/rnfail055.stderr b/testsuite/tests/rename/should_fail/rnfail055.stderr index 41a2bd095c..a995c5d2b9 100644 --- a/testsuite/tests/rename/should_fail/rnfail055.stderr +++ b/testsuite/tests/rename/should_fail/rnfail055.stderr @@ -6,42 +6,51 @@ RnFail055.hs-boot:1:73: Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. RnFail055.hs-boot:4:1: - Identifier ‛f1’ has conflicting definitions in the module and its hs-boot file + Identifier ‛f1’ has conflicting definitions in the module + and its hs-boot file Main module: f1 :: Int -> Float Boot file: f1 :: Float -> Int RnFail055.hs-boot:6:6: - Type constructor ‛S1’ has conflicting definitions in the module and its hs-boot file - Main module: type S1 a@R b@R = (a, b) - Boot file: type S1 a@R b@R c@R = (a, b) + Type constructor ‛S1’ has conflicting definitions in the module + and its hs-boot file + Main module: type S1 a b = (a, b) + Boot file: type S1 a b c = (a, b) RnFail055.hs-boot:8:6: - Type constructor ‛S2’ has conflicting definitions in the module and its hs-boot file - Main module: type S2 a@P b@R = forall a1. (a1, b) - Boot file: type S2 a@R b@R = forall b1. (a, b1) + Type constructor ‛S2’ has conflicting definitions in the module + and its hs-boot file + Main module: type S2 a b = forall a1. (a1, b) + Boot file: type S2 a b = forall b1. (a, b1) RnFail055.hs-boot:12:6: - Type constructor ‛T1’ has conflicting definitions in the module and its hs-boot file - Main module: data T1 a@R b@R + Type constructor ‛T1’ has conflicting definitions in the module + and its hs-boot file + Main module: data T1 a b No C type associated + Roles: [representational, representational] RecFlag Recursive, Promotable = T1 :: forall a b. [b] -> [a] -> T1 a b Stricts: _ _ FamilyInstance: none - Boot file: data T1 a@R b@R + Boot file: data T1 a b No C type associated + Roles: [representational, representational] RecFlag NonRecursive, Promotable = T1 :: forall a b. [a] -> [b] -> T1 a b Stricts: _ _ FamilyInstance: none RnFail055.hs-boot:14:16: - Type constructor ‛T2’ has conflicting definitions in the module and its hs-boot file - Main module: data Eq b => T2 a@R b@P + Type constructor ‛T2’ has conflicting definitions in the module + and its hs-boot file + Main module: data Eq b => T2 a b No C type associated + Roles: [representational, phantom] RecFlag Recursive, Promotable = T2 :: forall a b. a -> T2 a b Stricts: _ FamilyInstance: none - Boot file: data Eq a => T2 a@R b@R + Boot file: data Eq a => T2 a b No C type associated + Roles: [representational, representational] RecFlag NonRecursive, Promotable = T2 :: forall a b. a -> T2 a b Stricts: _ FamilyInstance: none @@ -53,20 +62,24 @@ RnFail055.hs-boot:17:12: T3' is exported by the hs-boot file, but not exported by the module RnFail055.hs-boot:21:6: - Type constructor ‛T5’ has conflicting definitions in the module and its hs-boot file - Main module: data T5 a@R + Type constructor ‛T5’ has conflicting definitions in the module + and its hs-boot file + Main module: data T5 a No C type associated + Roles: [representational] RecFlag Recursive, Promotable = T5 :: forall a. a -> T5 a Stricts: _ Fields: field5 FamilyInstance: none - Boot file: data T5 a@R + Boot file: data T5 a No C type associated + Roles: [representational] RecFlag NonRecursive, Promotable = T5 :: forall a. a -> T5 a Stricts: _ FamilyInstance: none RnFail055.hs-boot:23:6: - Type constructor ‛T6’ has conflicting definitions in the module and its hs-boot file + Type constructor ‛T6’ has conflicting definitions in the module + and its hs-boot file Main module: data T6 No C type associated RecFlag Recursive, Not promotable @@ -79,14 +92,17 @@ RnFail055.hs-boot:23:6: FamilyInstance: none RnFail055.hs-boot:25:6: - Type constructor ‛T7’ has conflicting definitions in the module and its hs-boot file - Main module: data T7 a@P + Type constructor ‛T7’ has conflicting definitions in the module + and its hs-boot file + Main module: data T7 a No C type associated + Roles: [phantom] RecFlag Recursive, Promotable = T7 :: forall a a1. a1 -> T7 a Stricts: _ FamilyInstance: none - Boot file: data T7 a@R + Boot file: data T7 a No C type associated + Roles: [representational] RecFlag NonRecursive, Promotable = T7 :: forall a. a -> T7 a Stricts: _ FamilyInstance: none @@ -95,15 +111,23 @@ RnFail055.hs-boot:27:22: RnFail055.m1 is exported by the hs-boot file, but not exported by the module RnFail055.hs-boot:28:7: - Class ‛C2’ has conflicting definitions in the module and its hs-boot file - Main module: class C2 a@R b@R + Class ‛C2’ has conflicting definitions in the module + and its hs-boot file + Main module: class C2 a b + Roles: [representational, representational] RecFlag Recursive m2 :: a -> b m2' :: a -> b - Boot file: class C2 a@R b@R + Boot file: class C2 a b + Roles: [representational, representational] RecFlag NonRecursive m2 :: a -> b RnFail055.hs-boot:29:24: - Class ‛C3’ has conflicting definitions in the module and its hs-boot file - Main module: class (Eq a, Ord a) => C3 a@R RecFlag Recursive - Boot file: class (Ord a, Eq a) => C3 a@R RecFlag NonRecursive + Class ‛C3’ has conflicting definitions in the module + and its hs-boot file + Main module: class (Eq a, Ord a) => C3 a + Roles: [representational] + RecFlag Recursive + Boot file: class (Ord a, Eq a) => C3 a + Roles: [representational] + RecFlag NonRecursive diff --git a/testsuite/tests/roles/Makefile b/testsuite/tests/roles/Makefile new file mode 100644 index 0000000000..9a36a1c5fe --- /dev/null +++ b/testsuite/tests/roles/Makefile @@ -0,0 +1,3 @@ +TOP=../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk diff --git a/testsuite/tests/roles/should_compile/Makefile b/testsuite/tests/roles/should_compile/Makefile new file mode 100644 index 0000000000..9101fbd40a --- /dev/null +++ b/testsuite/tests/roles/should_compile/Makefile @@ -0,0 +1,3 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk diff --git a/testsuite/tests/roles/should_compile/Roles1.hs b/testsuite/tests/roles/should_compile/Roles1.hs new file mode 100644 index 0000000000..ca040c4353 --- /dev/null +++ b/testsuite/tests/roles/should_compile/Roles1.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE RoleAnnotations, PolyKinds #-} + +module Roles1 where + +data T1 a = K1 a +data T2 a = K2 a +data T3 (a :: k) = K3 +data T4 (a :: * -> *) b = K4 (a b) + +data T5 a = K5 a +data T6 a = K6 +data T7 a b = K7 b + +type role T1 nominal +type role T2 representational +type role T3 phantom +type role T4 nominal _ +type role T5 _
\ No newline at end of file diff --git a/testsuite/tests/deriving/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr index 10edab13ef..e56cfb44b3 100644 --- a/testsuite/tests/deriving/should_compile/Roles1.stderr +++ b/testsuite/tests/roles/should_compile/Roles1.stderr @@ -1,44 +1,51 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * - data T1 a@N + data T1 a No C type associated + Roles: [nominal] RecFlag NonRecursive, Promotable = K1 :: forall a. a -> T1 a Stricts: _ FamilyInstance: none T2 :: * -> * - data T2 a@R + data T2 a No C type associated + Roles: [representational] RecFlag NonRecursive, Promotable = K2 :: forall a. a -> T2 a Stricts: _ FamilyInstance: none T3 :: forall (k :: BOX). k -> * - data T3 (k::BOX)@N (a::k)@P + data T3 (k::BOX) (a::k) No C type associated + Roles: [nominal, phantom] RecFlag NonRecursive, Not promotable = K3 :: forall (k::BOX) (a::k). T3 k a FamilyInstance: none T4 :: (* -> *) -> * -> * - data T4 (a::* -> *)@N b@N + data T4 (a::* -> *) b No C type associated + Roles: [nominal, nominal] RecFlag NonRecursive, Not promotable = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ FamilyInstance: none T5 :: * -> * - data T5 a@R + data T5 a No C type associated + Roles: [representational] RecFlag NonRecursive, Promotable = K5 :: forall a. a -> T5 a Stricts: _ FamilyInstance: none T6 :: forall (k :: BOX). k -> * - data T6 (k::BOX)@N (a::k)@P + data T6 (k::BOX) (a::k) No C type associated + Roles: [nominal, phantom] RecFlag NonRecursive, Not promotable = K6 :: forall (k::BOX) (a::k). T6 k a FamilyInstance: none T7 :: forall (k :: BOX). k -> * -> * - data T7 (k::BOX)@N (a::k)@P b@R + data T7 (k::BOX) (a::k) b No C type associated + Roles: [nominal, phantom, representational] RecFlag NonRecursive, Not promotable = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ FamilyInstance: none diff --git a/testsuite/tests/deriving/should_compile/Roles13.hs b/testsuite/tests/roles/should_compile/Roles13.hs index 70d4c0c7d0..70d4c0c7d0 100644 --- a/testsuite/tests/deriving/should_compile/Roles13.hs +++ b/testsuite/tests/roles/should_compile/Roles13.hs diff --git a/testsuite/tests/deriving/should_compile/Roles13.stderr b/testsuite/tests/roles/should_compile/Roles13.stderr index 647e59ba51..647e59ba51 100644 --- a/testsuite/tests/deriving/should_compile/Roles13.stderr +++ b/testsuite/tests/roles/should_compile/Roles13.stderr diff --git a/testsuite/tests/deriving/should_compile/Roles2.hs b/testsuite/tests/roles/should_compile/Roles2.hs index 1ead5a4e94..1ead5a4e94 100644 --- a/testsuite/tests/deriving/should_compile/Roles2.hs +++ b/testsuite/tests/roles/should_compile/Roles2.hs diff --git a/testsuite/tests/deriving/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr index 2dcf28e3bf..ac7a94bbfa 100644 --- a/testsuite/tests/deriving/should_compile/Roles2.stderr +++ b/testsuite/tests/roles/should_compile/Roles2.stderr @@ -1,14 +1,16 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * - data T1 a@R + data T1 a No C type associated + Roles: [representational] RecFlag NonRecursive, Not promotable = K1 :: forall a. (IO a) -> T1 a Stricts: _ FamilyInstance: none T2 :: * -> * - data T2 a@R + data T2 a No C type associated + Roles: [representational] RecFlag NonRecursive, Not promotable = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ FamilyInstance: none diff --git a/testsuite/tests/deriving/should_compile/Roles3.hs b/testsuite/tests/roles/should_compile/Roles3.hs index 4c26f0d986..4c26f0d986 100644 --- a/testsuite/tests/deriving/should_compile/Roles3.hs +++ b/testsuite/tests/roles/should_compile/Roles3.hs diff --git a/testsuite/tests/deriving/should_compile/Roles3.stderr b/testsuite/tests/roles/should_compile/Roles3.stderr index 1b187f4907..5a074179db 100644 --- a/testsuite/tests/deriving/should_compile/Roles3.stderr +++ b/testsuite/tests/roles/should_compile/Roles3.stderr @@ -1,28 +1,32 @@ TYPE SIGNATURES TYPE CONSTRUCTORS C1 :: * -> Constraint - class C1 a@R + class C1 a + Roles: [representational] RecFlag NonRecursive meth1 :: a -> a C2 :: * -> * -> Constraint - class C2 a@N b@N + class C2 a b + Roles: [nominal, nominal] RecFlag NonRecursive meth2 :: (~) * a b -> a -> b C3 :: * -> * -> Constraint - class C3 a@R b@N + class C3 a b + Roles: [representational, nominal] RecFlag NonRecursive - type family F3 b@N :: * + type family F3 b :: * meth3 :: a -> F3 b -> F3 b C4 :: * -> * -> Constraint - class C4 a@R b@N + class C4 a b + Roles: [representational, nominal] RecFlag NonRecursive meth4 :: a -> F4 b -> F4 b F4 :: * -> * - type family F4 a@N :: * + type family F4 a :: * Syn1 :: * -> * - type Syn1 a@N = F4 a + type Syn1 a = F4 a Syn2 :: * -> * - type Syn2 a@R = [a] + type Syn2 a = [a] COERCION AXIOMS axiom Roles3.NTCo:C1 :: C1 a = a -> a axiom Roles3.NTCo:C2 :: C2 a b = a ~ b => a -> b diff --git a/testsuite/tests/deriving/should_compile/Roles4.hs b/testsuite/tests/roles/should_compile/Roles4.hs index 32cb65a7df..b5c404a84c 100644 --- a/testsuite/tests/deriving/should_compile/Roles4.hs +++ b/testsuite/tests/roles/should_compile/Roles4.hs @@ -2,13 +2,15 @@ module Roles4 where -class C1 a@N where +type role C1 nominal +class C1 a where meth1 :: a -> a -class C2 a@R where +type role C2 representational +class C2 a where meth2 :: a -> a -type Syn1 a@N = [a] +type Syn1 a = [a] class C3 a where meth3 :: a -> Syn1 a diff --git a/testsuite/tests/deriving/should_compile/Roles4.stderr b/testsuite/tests/roles/should_compile/Roles4.stderr index 9969cbca12..5da8f04b26 100644 --- a/testsuite/tests/deriving/should_compile/Roles4.stderr +++ b/testsuite/tests/roles/should_compile/Roles4.stderr @@ -1,19 +1,22 @@ TYPE SIGNATURES TYPE CONSTRUCTORS C1 :: * -> Constraint - class C1 a@N + class C1 a + Roles: [nominal] RecFlag NonRecursive meth1 :: a -> a C2 :: * -> Constraint - class C2 a@R + class C2 a + Roles: [representational] RecFlag NonRecursive meth2 :: a -> a C3 :: * -> Constraint - class C3 a@N + class C3 a + Roles: [representational] RecFlag NonRecursive meth3 :: a -> Syn1 a Syn1 :: * -> * - type Syn1 a@N = [a] + type Syn1 a = [a] COERCION AXIOMS axiom Roles4.NTCo:C1 :: C1 a = a -> a axiom Roles4.NTCo:C2 :: C2 a = a -> a diff --git a/testsuite/tests/roles/should_compile/all.T b/testsuite/tests/roles/should_compile/all.T new file mode 100644 index 0000000000..eaa398d619 --- /dev/null +++ b/testsuite/tests/roles/should_compile/all.T @@ -0,0 +1,5 @@ +test('Roles1', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles2', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles3', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles4', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques']) diff --git a/testsuite/tests/roles/should_fail/Makefile b/testsuite/tests/roles/should_fail/Makefile new file mode 100644 index 0000000000..8f80de39c3 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Makefile @@ -0,0 +1,9 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +.PHONY: Roles12 + +Roles12: + '$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs-boot + -'$(TEST_HC)' $(TEST_HC_OPTS) -c Roles12.hs diff --git a/testsuite/tests/deriving/should_fail/Roles10.hs b/testsuite/tests/roles/should_fail/Roles10.hs index af19bfdf31..af19bfdf31 100644 --- a/testsuite/tests/deriving/should_fail/Roles10.hs +++ b/testsuite/tests/roles/should_fail/Roles10.hs diff --git a/testsuite/tests/deriving/should_fail/Roles10.stderr b/testsuite/tests/roles/should_fail/Roles10.stderr index 756aaa2e00..756aaa2e00 100644 --- a/testsuite/tests/deriving/should_fail/Roles10.stderr +++ b/testsuite/tests/roles/should_fail/Roles10.stderr diff --git a/testsuite/tests/deriving/should_fail/Roles11.hs b/testsuite/tests/roles/should_fail/Roles11.hs index c95cee798d..bc05477da9 100644 --- a/testsuite/tests/deriving/should_fail/Roles11.hs +++ b/testsuite/tests/roles/should_fail/Roles11.hs @@ -2,6 +2,7 @@ module Roles11 where -data T2 a@R where +type role T2 representational +data T2 a where K2 :: T2 Int diff --git a/testsuite/tests/roles/should_fail/Roles11.stderr b/testsuite/tests/roles/should_fail/Roles11.stderr new file mode 100644 index 0000000000..ee15f99185 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles11.stderr @@ -0,0 +1,5 @@ + +Roles11.hs:6:1: + Role mismatch on variable a: + Annotation says representational but role nominal is required + In the data declaration for ‛T2’ diff --git a/testsuite/tests/deriving/should_fail/Roles12.hs b/testsuite/tests/roles/should_fail/Roles12.hs index 875d105b78..875d105b78 100644 --- a/testsuite/tests/deriving/should_fail/Roles12.hs +++ b/testsuite/tests/roles/should_fail/Roles12.hs diff --git a/testsuite/tests/deriving/should_fail/Roles12.hs-boot b/testsuite/tests/roles/should_fail/Roles12.hs-boot index 6a708d984a..6a708d984a 100644 --- a/testsuite/tests/deriving/should_fail/Roles12.hs-boot +++ b/testsuite/tests/roles/should_fail/Roles12.hs-boot diff --git a/testsuite/tests/deriving/should_fail/Roles12.stderr b/testsuite/tests/roles/should_fail/Roles12.stderr index ad8c25eecb..42d63463e0 100644 --- a/testsuite/tests/deriving/should_fail/Roles12.stderr +++ b/testsuite/tests/roles/should_fail/Roles12.stderr @@ -2,12 +2,14 @@ Roles12.hs:5:6: Type constructor ‛T’ has conflicting definitions in the module and its hs-boot file - Main module: data T a@P + Main module: data T a No C type associated + Roles: [phantom] RecFlag Recursive, Promotable = FamilyInstance: none - Boot file: abstract(False) T a@R + Boot file: abstract(False) T a No C type associated + Roles: [representational] RecFlag NonRecursive, Not promotable FamilyInstance: none diff --git a/testsuite/tests/roles/should_fail/Roles5.hs b/testsuite/tests/roles/should_fail/Roles5.hs new file mode 100644 index 0000000000..b75af75008 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles5.hs @@ -0,0 +1,9 @@ +module Roles5 where + +data T a +class C a +type S a = Int + +type role T nominal +type role C representational +type role S phantom
\ No newline at end of file diff --git a/testsuite/tests/roles/should_fail/Roles5.stderr b/testsuite/tests/roles/should_fail/Roles5.stderr new file mode 100644 index 0000000000..c4907c89f6 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles5.stderr @@ -0,0 +1,12 @@ + +Roles5.hs:7:1: + Illegal role annotation for T; + did you intend to use RoleAnnotations? + +Roles5.hs:8:1: + Illegal role annotation for C; + did you intend to use RoleAnnotations? + +Roles5.hs:9:1: + Illegal role annotation for S; + they are allowed only for datatypes and classes. diff --git a/testsuite/tests/roles/should_fail/Roles6.hs b/testsuite/tests/roles/should_fail/Roles6.hs new file mode 100644 index 0000000000..c0ab9fafb2 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles6.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE RoleAnnotations #-} + +module Roles6 where + +data Foo a b = MkFoo (a b) + +type role Foo nominal representational phantom + diff --git a/testsuite/tests/roles/should_fail/Roles6.stderr b/testsuite/tests/roles/should_fail/Roles6.stderr new file mode 100644 index 0000000000..3cca04d2a6 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles6.stderr @@ -0,0 +1,15 @@ + +Roles6.hs:5:1: + Role mismatch on variable a: + Annotation says nominal but role representational is required + In the data declaration for ‛Foo’ + +Roles6.hs:5:1: + Role mismatch on variable b: + Annotation says representational but role nominal is required + In the data declaration for ‛Foo’ + +Roles6.hs:7:1: + Wrong number of roles listed in role annotation; + Expected 2, got 3: + type role Foo nominal representational phantom diff --git a/testsuite/tests/roles/should_fail/Roles7.hs b/testsuite/tests/roles/should_fail/Roles7.hs new file mode 100644 index 0000000000..221b01a1c5 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles7.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE RoleAnnotations #-} + +module Roles7 where + +class Bar a +type role Bar repesentational + -- spelling error intentional!
\ No newline at end of file diff --git a/testsuite/tests/roles/should_fail/Roles7.stderr b/testsuite/tests/roles/should_fail/Roles7.stderr new file mode 100644 index 0000000000..e4774f1aa8 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles7.stderr @@ -0,0 +1,4 @@ + +Roles7.hs:6:15: + Illegal role name ‛repesentational’ + Perhaps you meant ‛representational’ diff --git a/testsuite/tests/roles/should_fail/Roles8.hs b/testsuite/tests/roles/should_fail/Roles8.hs new file mode 100644 index 0000000000..396431cd50 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles8.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE RoleAnnotations, GADTs #-} + +module Roles8 where + +data T1 a = K1 a + +type role T1 nominal +type role T1 nominal + +data T2 b = MkT2 + +type role T2 representational +type role T2 phantom
\ No newline at end of file diff --git a/testsuite/tests/roles/should_fail/Roles8.stderr b/testsuite/tests/roles/should_fail/Roles8.stderr new file mode 100644 index 0000000000..22f66f4667 --- /dev/null +++ b/testsuite/tests/roles/should_fail/Roles8.stderr @@ -0,0 +1,10 @@ + +Roles8.hs:7:1: + Duplicate role annotations for ‛T1’: + type role T1 nominal -- written at Roles8.hs:7:1-20 + type role T1 nominal -- written at Roles8.hs:8:1-20 + +Roles8.hs:12:1: + Duplicate role annotations for ‛T2’: + type role T2 representational -- written at Roles8.hs:12:1-29 + type role T2 phantom -- written at Roles8.hs:13:1-20 diff --git a/testsuite/tests/deriving/should_fail/Roles9.hs b/testsuite/tests/roles/should_fail/Roles9.hs index 86d10a3063..f8e134d5a1 100644 --- a/testsuite/tests/deriving/should_fail/Roles9.hs +++ b/testsuite/tests/roles/should_fail/Roles9.hs @@ -2,7 +2,8 @@ module Roles9 where -class C a@N where +type role C nominal +class C a where meth :: a -> a instance C Int where diff --git a/testsuite/tests/deriving/should_fail/Roles9.stderr b/testsuite/tests/roles/should_fail/Roles9.stderr index 43c3dc7da3..0cd02f9b5f 100644 --- a/testsuite/tests/deriving/should_fail/Roles9.stderr +++ b/testsuite/tests/roles/should_fail/Roles9.stderr @@ -1,5 +1,5 @@ -Roles9.hs:12:12: +Roles9.hs:13:12: Can't make a derived instance of ‛C Age’ (even with cunning newtype deriving): it is not type-safe to use GeneralizedNewtypeDeriving on this class; diff --git a/testsuite/tests/roles/should_fail/all.T b/testsuite/tests/roles/should_fail/all.T new file mode 100644 index 0000000000..36f2d2e1a4 --- /dev/null +++ b/testsuite/tests/roles/should_fail/all.T @@ -0,0 +1,10 @@ +test('Roles5', normal, compile_fail, ['']) +test('Roles6', normal, compile_fail, ['']) +test('Roles7', normal, compile_fail, ['']) +test('Roles8', normal, compile_fail, ['']) +test('Roles9', normal, compile_fail, ['']) +test('Roles10', normal, compile_fail, ['']) +test('Roles11', normal, compile_fail, ['']) +test('Roles12', + extra_clean(['Roles12.o-boot', 'Roles12.hi-boot']), + run_command, ['$MAKE --no-print-directory -s Roles12']) diff --git a/testsuite/tests/th/T1835.stdout b/testsuite/tests/th/T1835.stdout index cbe455bca1..ba8e65f418 100644 --- a/testsuite/tests/th/T1835.stdout +++ b/testsuite/tests/th/T1835.stdout @@ -1,4 +1,4 @@ -class GHC.Classes.Eq a_0 => Main.MyClass a_0@R +class GHC.Classes.Eq a_0 => Main.MyClass a_0 instance Main.MyClass Main.Foo instance Main.MyClass Main.Baz instance GHC.Classes.Eq a_1 => Main.MyClass (Main.Quux a_1) diff --git a/testsuite/tests/th/T4188.stderr b/testsuite/tests/th/T4188.stderr index 187d902ac1..02b997788b 100644 --- a/testsuite/tests/th/T4188.stderr +++ b/testsuite/tests/th/T4188.stderr @@ -1,6 +1,6 @@ -data T4188.T1 a_0@R = forall b_1 . T4188.MkT1 a_0 b_1 -data T4188.T2 a_0@R +data T4188.T1 a_0 = forall b_1 . T4188.MkT1 a_0 b_1 +data T4188.T2 a_0 = forall b_1 . (T4188.C a_0, T4188.C b_1) => T4188.MkT2 a_0 b_1 -data T4188.T3 x_0@N +data T4188.T3 x_0 = forall x_1 y_2 . (x_0 ~ (x_1, y_2), T4188.C x_1, T4188.C y_2) => T4188.MkT3 x_1 y_2 diff --git a/testsuite/tests/th/TH_Roles1.hs b/testsuite/tests/th/TH_Roles1.hs index 5829895f59..d746fc9cd8 100644 --- a/testsuite/tests/th/TH_Roles1.hs +++ b/testsuite/tests/th/TH_Roles1.hs @@ -4,5 +4,6 @@ module TH_Roles1 where import Language.Haskell.TH -$( return [DataD [] (mkName "T") [RoledTV (mkName "a") Representational] [] []] ) +$( return [ DataD [] (mkName "T") [PlainTV (mkName "a")] [] [] + , RoleAnnotD (mkName "T") [RepresentationalR] ] ) diff --git a/testsuite/tests/th/TH_Roles1.stderr b/testsuite/tests/th/TH_Roles1.stderr index f8b659e417..47105b211d 100644 --- a/testsuite/tests/th/TH_Roles1.stderr +++ b/testsuite/tests/th/TH_Roles1.stderr @@ -1,5 +1,4 @@ TH_Roles1.hs:7:4: - Illegal role annotation - Perhaps you intended to use RoleAnnotations - In the data type declaration for ‛T’ + Illegal role annotation for T; + did you intend to use RoleAnnotations? diff --git a/testsuite/tests/th/TH_Roles2.hs b/testsuite/tests/th/TH_Roles2.hs index fc010df9ed..30f4fc7631 100644 --- a/testsuite/tests/th/TH_Roles2.hs +++ b/testsuite/tests/th/TH_Roles2.hs @@ -4,5 +4,6 @@ module TH_Roles2 where import Language.Haskell.TH -$( return [DataD [] (mkName "T") [KindedRoledTV (mkName "a") (VarT (mkName "k")) Representational] [] []] ) +$( return [ DataD [] (mkName "T") [KindedTV (mkName "a") (VarT (mkName "k"))] [] [] + , RoleAnnotD (mkName "T") [RepresentationalR] ] ) diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index f7e473e16b..b828ed14b5 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -1,8 +1,9 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T :: forall (k :: BOX). k -> * - data T (k::BOX)@N (a::k)@R + data T (k::BOX) (a::k) No C type associated + Roles: [nominal, representational] RecFlag NonRecursive, Not promotable = FamilyInstance: none diff --git a/testsuite/tests/th/TH_Roles3.hs b/testsuite/tests/th/TH_Roles3.hs index 355b1e595a..e42394eb02 100644 --- a/testsuite/tests/th/TH_Roles3.hs +++ b/testsuite/tests/th/TH_Roles3.hs @@ -4,6 +4,7 @@ module Roles3 where import Language.Haskell.TH -$( do { decls <- [d| data Foo a (b :: k) c@R (d :: k)@N |] - ; reportWarning (pprint decls) +$( do { decls <- [d| data Foo a (b :: k) c (d :: k) + type role Foo _ _ representational nominal |] + ; runIO $ putStrLn (pprint decls) ; return decls }) diff --git a/testsuite/tests/th/TH_Roles3.stderr b/testsuite/tests/th/TH_Roles3.stderr index b1bfd20825..d3f71d22ba 100644 --- a/testsuite/tests/th/TH_Roles3.stderr +++ b/testsuite/tests/th/TH_Roles3.stderr @@ -1,3 +1,2 @@ - -TH_Roles3.hs:7:4: Warning: - data Foo_0 a_1 (b_2 :: k_3) c_4@R (d_5 :: k_3)@N +data Foo_0 a_1 (b_2 :: k_3) c_4 (d_5 :: k_3) +type role Foo_0 _ _ representational nominal diff --git a/testsuite/tests/th/TH_Roles4.hs b/testsuite/tests/th/TH_Roles4.hs new file mode 100644 index 0000000000..cc7fce15a1 --- /dev/null +++ b/testsuite/tests/th/TH_Roles4.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TemplateHaskell #-} + +module Roles4 where + +import Language.Haskell.TH + +data Sticky a b = MkSticky (a b) + +$( do roles <- reifyRoles (mkName "Sticky") + runIO $ putStrLn (show roles) + return [] )
\ No newline at end of file diff --git a/testsuite/tests/th/TH_Roles4.stderr b/testsuite/tests/th/TH_Roles4.stderr new file mode 100644 index 0000000000..1c988e89e8 --- /dev/null +++ b/testsuite/tests/th/TH_Roles4.stderr @@ -0,0 +1 @@ +[RepresentationalR,NominalR] diff --git a/testsuite/tests/th/TH_reifyDecl1.stderr b/testsuite/tests/th/TH_reifyDecl1.stderr index 0f44e4b862..82a4f572ce 100644 --- a/testsuite/tests/th/TH_reifyDecl1.stderr +++ b/testsuite/tests/th/TH_reifyDecl1.stderr @@ -1,9 +1,9 @@ data TH_reifyDecl1.T = TH_reifyDecl1.A | TH_reifyDecl1.B -data TH_reifyDecl1.R a_0@R = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D -data TH_reifyDecl1.List a_0@R +data TH_reifyDecl1.R a_0 = TH_reifyDecl1.C a_0 | TH_reifyDecl1.D +data TH_reifyDecl1.List a_0 = TH_reifyDecl1.Nil | TH_reifyDecl1.Cons a_0 (TH_reifyDecl1.List a_0) -data TH_reifyDecl1.Tree a_0@P +data TH_reifyDecl1.Tree a_0 = TH_reifyDecl1.Leaf | (TH_reifyDecl1.Tree a_0) TH_reifyDecl1.:+: (TH_reifyDecl1.Tree a_0) type TH_reifyDecl1.IntList = [GHC.Types.Int] @@ -12,14 +12,14 @@ Constructor from TH_reifyDecl1.Tree: TH_reifyDecl1.Leaf :: forall a_0 . TH_reify Class op from TH_reifyDecl1.C1: TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 => a_0 -> GHC.Types.Int infixl 3 TH_reifyDecl1.m1 -class TH_reifyDecl1.C1 a_0@R +class TH_reifyDecl1.C1 a_0 where TH_reifyDecl1.m1 :: forall a_0 . TH_reifyDecl1.C1 a_0 => a_0 -> GHC.Types.Int -class TH_reifyDecl1.C2 a_0@R +class TH_reifyDecl1.C2 a_0 where TH_reifyDecl1.m2 :: forall a_0 . TH_reifyDecl1.C2 a_0 => a_0 -> GHC.Types.Int instance TH_reifyDecl1.C2 GHC.Types.Int -class TH_reifyDecl1.C3 a_0@N +class TH_reifyDecl1.C3 a_0 instance TH_reifyDecl1.C3 GHC.Types.Int type family TH_reifyDecl1.AT1 a_0 :: * -> * type instance TH_reifyDecl1.AT1 GHC.Types.Int = GHC.Types.Bool diff --git a/testsuite/tests/th/TH_reifyDecl2.stderr b/testsuite/tests/th/TH_reifyDecl2.stderr index 65bbd75dd5..802cf293c6 100644 --- a/testsuite/tests/th/TH_reifyDecl2.stderr +++ b/testsuite/tests/th/TH_reifyDecl2.stderr @@ -1,2 +1,2 @@ -data Data.Maybe.Maybe a_0@R +data Data.Maybe.Maybe a_0 = Data.Maybe.Nothing | Data.Maybe.Just a_0 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 455f45d713..d3d0db01bb 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -285,5 +285,6 @@ test('T8028', test('TH_Roles1', normal, compile_fail, ['-v0']) test('TH_Roles2', normal, compile, ['-v0 -ddump-tc']) test('TH_Roles3', normal, compile, ['-v0 -dsuppress-uniques']) +test('TH_Roles4', normal, compile, ['-v0']) test('T8186', normal, compile_and_run, ['-v0'])
\ No newline at end of file diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr index 92155f0588..45aaeaf131 100644 --- a/testsuite/tests/typecheck/should_compile/tc231.stderr +++ b/testsuite/tests/typecheck/should_compile/tc231.stderr @@ -6,20 +6,23 @@ TYPE SIGNATURES s :: forall t t1. Q t (Z [Char]) t1 -> Q t (Z [Char]) t1 TYPE CONSTRUCTORS Q :: * -> * -> * -> * - data Q s@R a@R chain@R + data Q s a chain No C type associated + Roles: [representational, representational, representational] RecFlag NonRecursive, Promotable = Node :: forall s a chain. s -> a -> chain -> Q s a chain Stricts: _ _ _ FamilyInstance: none Z :: * -> * - data Z a@R + data Z a No C type associated + Roles: [representational] RecFlag NonRecursive, Promotable = Z :: forall a. a -> Z a Stricts: _ FamilyInstance: none Zork :: * -> * -> * -> Constraint - class Zork s@N a@R b@P | a -> b + class Zork s a b | a -> b + Roles: [nominal, representational, phantom] RecFlag NonRecursive huh :: forall chain. Q s a chain -> ST s () COERCION AXIOMS diff --git a/testsuite/tests/typecheck/should_fail/T3468.stderr b/testsuite/tests/typecheck/should_fail/T3468.stderr index e12db7a747..fb6f43bd74 100644 --- a/testsuite/tests/typecheck/should_fail/T3468.stderr +++ b/testsuite/tests/typecheck/should_fail/T3468.stderr @@ -1,8 +1,10 @@ T3468.hs-boot:3:6: - Type constructor ‛Tool’ has conflicting definitions in the module and its hs-boot file - Main module: data Tool d@P + Type constructor ‛Tool’ has conflicting definitions in the module + and its hs-boot file + Main module: data Tool d No C type associated + Roles: [phantom] RecFlag Recursive, Promotable = F :: forall d a. a -> Tool d Stricts: _ FamilyInstance: none diff --git a/testsuite/tests/typecheck/should_fail/T7892.stderr b/testsuite/tests/typecheck/should_fail/T7892.stderr index 882aca64d6..eec7bd73dc 100644 --- a/testsuite/tests/typecheck/should_fail/T7892.stderr +++ b/testsuite/tests/typecheck/should_fail/T7892.stderr @@ -1,2 +1,2 @@ -T7892.hs:5:4: Couldn't match kind ‛* -> *’ against ‛*’ +T7892.hs:5:4: Couldn't match kind ‛*’ against ‛* -> *’ diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs index 54d5d2fc1a..082fbadebf 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs @@ -5,7 +5,8 @@ import Data.Ord (Down) newtype Age = Age Int deriving Show -data Map a@N b = Map a b deriving Show +type role Map nominal _ +data Map a b = Map a b deriving Show foo1 = coerce $ one :: () diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr index ecc9577782..642b1d8513 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr @@ -1,5 +1,5 @@ -TcCoercibleFail.hs:10:8: +TcCoercibleFail.hs:11:8: No instance for (Coercible Int ()) because ‛Int’ and ‛()’ are different types. arising from a use of ‛coerce’ @@ -7,18 +7,18 @@ TcCoercibleFail.hs:10:8: In the expression: coerce $ one :: () In an equation for ‛foo1’: foo1 = coerce $ one :: () -TcCoercibleFail.hs:13:8: +TcCoercibleFail.hs:14:8: Could not deduce (Coercible (m Int) (m Age)) because ‛m Int’ and ‛m Age’ are different types. arising from a use of ‛coerce’ from the context (Monad m) bound by the type signature for foo2 :: Monad m => m Age - at TcCoercibleFail.hs:12:9-34 + at TcCoercibleFail.hs:13:9-34 In the expression: coerce In the expression: coerce $ (return one :: m Int) In an equation for ‛foo2’: foo2 = coerce $ (return one :: m Int) -TcCoercibleFail.hs:15:8: +TcCoercibleFail.hs:16:8: No instance for (Coercible (Map Int ()) (Map Age ())) because the first type argument of ‛Map’ has role Nominal, but the arguments ‛Int’ and ‛Age’ differ @@ -27,7 +27,7 @@ TcCoercibleFail.hs:15:8: In the expression: coerce $ Map one () :: Map Age () In an equation for ‛foo3’: foo3 = coerce $ Map one () :: Map Age () -TcCoercibleFail.hs:17:8: +TcCoercibleFail.hs:18:8: No instance for (Coercible Int (Down Int)) because the constructor of ‛Down’ is not imported arising from a use of ‛coerce’ @@ -35,7 +35,7 @@ TcCoercibleFail.hs:17:8: In the expression: coerce $ one :: Down Int In an equation for ‛foo4’: foo4 = coerce $ one :: Down Int -TcCoercibleFail.hs:21:8: +TcCoercibleFail.hs:22:8: No instance for (Coercible (Void ()) ()) because ‛Void’ is a recursive type constuctor arising from a use of ‛coerce’ |