summaryrefslogtreecommitdiff
path: root/testsuite/tests/deriving/should_compile
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/deriving/should_compile')
-rw-r--r--testsuite/tests/deriving/should_compile/T11416.hs4
-rw-r--r--testsuite/tests/deriving/should_compile/T11732c.hs6
-rw-r--r--testsuite/tests/deriving/should_compile/T11833.hs6
-rw-r--r--testsuite/tests/deriving/should_compile/T12144_1.hs4
-rw-r--r--testsuite/tests/deriving/should_compile/T13297.hs4
-rw-r--r--testsuite/tests/deriving/should_compile/T13758.hs3
-rw-r--r--testsuite/tests/deriving/should_compile/T14933.hs4
-rw-r--r--testsuite/tests/deriving/should_compile/T8165.hs6
-rw-r--r--testsuite/tests/deriving/should_compile/T8678.hs4
-rw-r--r--testsuite/tests/deriving/should_compile/T9359.hs4
-rw-r--r--testsuite/tests/deriving/should_compile/deriving-via-standalone.hs9
11 files changed, 36 insertions, 18 deletions
diff --git a/testsuite/tests/deriving/should_compile/T11416.hs b/testsuite/tests/deriving/should_compile/T11416.hs
index 210d0423b7..6666764e3d 100644
--- a/testsuite/tests/deriving/should_compile/T11416.hs
+++ b/testsuite/tests/deriving/should_compile/T11416.hs
@@ -8,7 +8,7 @@ import Data.Kind
type ConstantT a b = a
-newtype T f (a :: ConstantT * f) = T (f a)
+newtype T f (a :: ConstantT Type f) = T (f a)
deriving Functor
data family TFam1 (f :: k1) (a :: k2)
@@ -16,5 +16,5 @@ newtype instance TFam1 f (ConstantT a f) = TFam1 (f a)
deriving Functor
data family TFam2 (f :: k1) (a :: k2)
-newtype instance TFam2 f (a :: ConstantT * f) = TFam2 (f a)
+newtype instance TFam2 f (a :: ConstantT Type f) = TFam2 (f a)
deriving Functor
diff --git a/testsuite/tests/deriving/should_compile/T11732c.hs b/testsuite/tests/deriving/should_compile/T11732c.hs
index 55553045c0..c4dedf52d2 100644
--- a/testsuite/tests/deriving/should_compile/T11732c.hs
+++ b/testsuite/tests/deriving/should_compile/T11732c.hs
@@ -6,15 +6,15 @@ module T11732c where
import Data.Kind
-class Cat k (cat :: k -> k -> *) where
+class Cat k (cat :: k -> k -> Type) where
catId :: cat a a
catComp :: cat b c -> cat a b -> cat a c
-instance Cat * (->) where
+instance Cat Type (->) where
catId = id
catComp = (.)
-newtype Fun2 a b = Fun2 (a -> b) deriving (Cat *)
+newtype Fun2 a b = Fun2 (a -> b) deriving (Cat Type)
-- The ticket says this should work:
-- newtype Fun1 a b = Fun1 (a -> b) deriving (Cat k)
diff --git a/testsuite/tests/deriving/should_compile/T11833.hs b/testsuite/tests/deriving/should_compile/T11833.hs
index 75d2a2d255..0097f54a30 100644
--- a/testsuite/tests/deriving/should_compile/T11833.hs
+++ b/testsuite/tests/deriving/should_compile/T11833.hs
@@ -2,8 +2,10 @@
{-# LANGUAGE PolyKinds #-}
module T11833 where
-class Category (cat :: k -> k -> *) where
+import Data.Kind (Type)
+
+class Category (cat :: k -> k -> Type) where
catId :: cat a a
catComp :: cat b c -> cat a b -> cat a c
-newtype T (c :: * -> * -> *) a b = MkT (c a b) deriving Category
+newtype T (c :: Type -> Type -> Type) a b = MkT (c a b) deriving Category
diff --git a/testsuite/tests/deriving/should_compile/T12144_1.hs b/testsuite/tests/deriving/should_compile/T12144_1.hs
index f43d84ae6d..3b0b9ce930 100644
--- a/testsuite/tests/deriving/should_compile/T12144_1.hs
+++ b/testsuite/tests/deriving/should_compile/T12144_1.hs
@@ -2,5 +2,7 @@
{-# LANGUAGE KindSignatures #-}
module T12144_1 where
-class C (a :: * -> *)
+import Data.Kind (Type)
+
+class C (a :: Type -> Type)
data T a = MkT (a -> Int) deriving C
diff --git a/testsuite/tests/deriving/should_compile/T13297.hs b/testsuite/tests/deriving/should_compile/T13297.hs
index 604a64971f..bda39db24d 100644
--- a/testsuite/tests/deriving/should_compile/T13297.hs
+++ b/testsuite/tests/deriving/should_compile/T13297.hs
@@ -1,9 +1,11 @@
{-# Language TypeFamilies, StandaloneDeriving, GeneralizedNewtypeDeriving, UndecidableInstances #-}
module T13297 where
+import Data.Kind (Type)
+
newtype N p m a = N (((CT p) m) a)
deriving instance (CT p ~ f, Functor (f m)) => Functor (N p m)
deriving instance (CT p ~ f, Applicative (f m)) => Applicative (N p m) -- panic when this line added
class C p where
- type CT p :: (* -> *) -> * -> *
+ type CT p :: (Type -> Type) -> Type -> Type
diff --git a/testsuite/tests/deriving/should_compile/T13758.hs b/testsuite/tests/deriving/should_compile/T13758.hs
index 91ddd99b77..62825bd107 100644
--- a/testsuite/tests/deriving/should_compile/T13758.hs
+++ b/testsuite/tests/deriving/should_compile/T13758.hs
@@ -5,6 +5,9 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
+
+{-# OPTIONS -Wno-noncanonical-monoid-instances #-}
+
module T13758 where
import Data.Coerce
diff --git a/testsuite/tests/deriving/should_compile/T14933.hs b/testsuite/tests/deriving/should_compile/T14933.hs
index 2682d6242f..de8562d189 100644
--- a/testsuite/tests/deriving/should_compile/T14933.hs
+++ b/testsuite/tests/deriving/should_compile/T14933.hs
@@ -3,8 +3,10 @@
{-# LANGUAGE TypeFamilies #-}
module T14933 where
+import Data.Kind (Type)
+
class Wrapped s where
- type Unwrapped s :: *
+ type Unwrapped s :: Type
class Fork m where
fork :: (x, m)
diff --git a/testsuite/tests/deriving/should_compile/T8165.hs b/testsuite/tests/deriving/should_compile/T8165.hs
index dd56002648..a7292be2f7 100644
--- a/testsuite/tests/deriving/should_compile/T8165.hs
+++ b/testsuite/tests/deriving/should_compile/T8165.hs
@@ -5,6 +5,8 @@
{-# LANGUAGE UndecidableInstances #-}
module T8165 where
+import Data.Kind (Type)
+
-----------------------------------------------------------
class C a where
@@ -30,8 +32,8 @@ newtype E = MkE Int
-----------------------------------------------------------
class C2 a b where
- type F b c a :: *
- type G b (d :: * -> *) :: * -> *
+ type F b c a :: Type
+ type G b (d :: Type -> Type) :: Type -> Type
instance C2 a y => C2 a (Either x y) where
type F (Either x y) c a = F y c a
diff --git a/testsuite/tests/deriving/should_compile/T8678.hs b/testsuite/tests/deriving/should_compile/T8678.hs
index 655f530b5b..29e73b4a49 100644
--- a/testsuite/tests/deriving/should_compile/T8678.hs
+++ b/testsuite/tests/deriving/should_compile/T8678.hs
@@ -1,10 +1,12 @@
{-# LANGUAGE DataKinds, DeriveFunctor, FlexibleInstances, GADTs, KindSignatures, StandaloneDeriving #-}
module T8678 where
+import Data.Kind (Type)
+
data {- kind -} Nat = Z | S Nat
-- GADT in parameter other than the last
-data NonStandard :: Nat -> * -> * -> * where
+data NonStandard :: Nat -> Type -> Type -> Type where
Standard :: a -> NonStandard (S n) a b
Non :: NonStandard n a b -> b -> NonStandard (S n) a b
diff --git a/testsuite/tests/deriving/should_compile/T9359.hs b/testsuite/tests/deriving/should_compile/T9359.hs
index 313d66e1ca..d541677911 100644
--- a/testsuite/tests/deriving/should_compile/T9359.hs
+++ b/testsuite/tests/deriving/should_compile/T9359.hs
@@ -1,12 +1,14 @@
{-# Language GADTs, PolyKinds, TypeFamilies, DataKinds #-}
module Fam where
+import Data.Kind (Type)
+
data Cmp a where
Sup :: Cmp a
V :: a -> Cmp a
deriving (Show, Eq)
-data family CmpInterval (a :: Cmp k) (b :: Cmp k) :: *
+data family CmpInterval (a :: Cmp k) (b :: Cmp k) :: Type
data instance CmpInterval (V c) Sup = Starting c
deriving( Show )
diff --git a/testsuite/tests/deriving/should_compile/deriving-via-standalone.hs b/testsuite/tests/deriving/should_compile/deriving-via-standalone.hs
index 0fa71d7e36..26484a2df2 100644
--- a/testsuite/tests/deriving/should_compile/deriving-via-standalone.hs
+++ b/testsuite/tests/deriving/should_compile/deriving-via-standalone.hs
@@ -8,27 +8,28 @@
{-# LANGUAGE StandaloneDeriving #-}
module DerivingViaStandalone where
+import Data.Kind (Type)
import Control.Applicative
import Data.Functor.Compose
import Data.Proxy
import Data.Semigroup
-newtype App (f :: * -> *) a = App (f a)
+newtype App (f :: Type -> Type) a = App (f a)
deriving newtype
(Functor, Applicative)
instance (Applicative f, Semigroup a) => Semigroup (App f a) where
(<>) = liftA2 (<>)
-deriving via (App (Compose (f :: * -> *) g) a)
+deriving via (App (Compose (f :: Type -> Type) g) a)
instance (Applicative f, Applicative g, Semigroup a)
=> Semigroup (Compose f g a)
-class C (a :: k -> *)
+class C (a :: k -> Type)
instance C Proxy
newtype MyProxy a = MyProxy (Proxy a)
-deriving via (Proxy :: * -> *) instance C MyProxy
+deriving via (Proxy :: Type -> Type) instance C MyProxy
class Z a b
data T a