diff options
Diffstat (limited to 'testsuite/tests/ghci/scripts')
-rw-r--r-- | testsuite/tests/ghci/scripts/T10321.hs | 3 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T11252.script | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T11376.script | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T12550.script | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T13407.script | 4 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T13963.script | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T13988.hs | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T7873.script | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T7939.hs | 4 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T8357.hs | 7 |
10 files changed, 16 insertions, 14 deletions
diff --git a/testsuite/tests/ghci/scripts/T10321.hs b/testsuite/tests/ghci/scripts/T10321.hs index 44d264a801..443ebe41a4 100644 --- a/testsuite/tests/ghci/scripts/T10321.hs +++ b/testsuite/tests/ghci/scripts/T10321.hs @@ -5,9 +5,10 @@ module T10321 where +import Data.Kind (Type) import GHC.TypeLits -data Vec :: Nat -> * -> * where +data Vec :: Nat -> Type -> Type where Nil :: Vec 0 a (:>) :: a -> Vec n a -> Vec (n + 1) a diff --git a/testsuite/tests/ghci/scripts/T11252.script b/testsuite/tests/ghci/scripts/T11252.script index 485cd8fa0d..3cec1d348d 100644 --- a/testsuite/tests/ghci/scripts/T11252.script +++ b/testsuite/tests/ghci/scripts/T11252.script @@ -1,3 +1,3 @@ -:set -XTypeInType +:set -XPolyKinds data Proxy1 k (a :: k) = Proxy1 :kind Proxy1 diff --git a/testsuite/tests/ghci/scripts/T11376.script b/testsuite/tests/ghci/scripts/T11376.script index d359b66542..0cda4f02ba 100644 --- a/testsuite/tests/ghci/scripts/T11376.script +++ b/testsuite/tests/ghci/scripts/T11376.script @@ -3,7 +3,7 @@ let { bar :: Show a => a -> b -> a; bar = error "urk" } :type bar @Int :set -fprint-explicit-foralls :type bar @Int -:set -fprint-explicit-kinds -XTypeApplications -XTypeInType +:set -fprint-explicit-kinds -XTypeApplications -XPolyKinds data Prox a = Prox let { prox :: Prox a; prox = Prox } :t prox diff --git a/testsuite/tests/ghci/scripts/T12550.script b/testsuite/tests/ghci/scripts/T12550.script index dad2a47e65..7c07e8f1dd 100644 --- a/testsuite/tests/ghci/scripts/T12550.script +++ b/testsuite/tests/ghci/scripts/T12550.script @@ -1,4 +1,4 @@ -:set -fprint-explicit-foralls -XKindSignatures -XExplicitNamespaces +:set -fprint-explicit-foralls -XKindSignatures -XExplicitNamespaces -XUnicodeSyntax import Data.Kind (type Type) diff --git a/testsuite/tests/ghci/scripts/T13407.script b/testsuite/tests/ghci/scripts/T13407.script index f77fd42afe..3956a3a210 100644 --- a/testsuite/tests/ghci/scripts/T13407.script +++ b/testsuite/tests/ghci/scripts/T13407.script @@ -1,4 +1,4 @@ -:set -XTypeInType -XRankNTypes +:set -XPolyKinds -XRankNTypes import Data.Kind -data Foo :: (* -> *) -> (forall k. k -> *) +data Foo :: (Type -> Type) -> (forall k. k -> Type) :info Foo diff --git a/testsuite/tests/ghci/scripts/T13963.script b/testsuite/tests/ghci/scripts/T13963.script index fdd4d78338..c5e830aad1 100644 --- a/testsuite/tests/ghci/scripts/T13963.script +++ b/testsuite/tests/ghci/scripts/T13963.script @@ -1,4 +1,4 @@ -:set -XTypeInType -XRankNTypes +:set -XPolyKinds -XDataKinds -XRankNTypes import GHC.Exts (TYPE, RuntimeRep(LiftedRep)) type Pair (a :: TYPE rep) (b :: TYPE rep') rep'' = forall (r :: TYPE rep''). (a -> b -> r) :kind Pair diff --git a/testsuite/tests/ghci/scripts/T13988.hs b/testsuite/tests/ghci/scripts/T13988.hs index 54969cad4d..d26135e26d 100644 --- a/testsuite/tests/ghci/scripts/T13988.hs +++ b/testsuite/tests/ghci/scripts/T13988.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeInType, GADTs #-} +{-# LANGUAGE PolyKinds, GADTs #-} module T13988 where diff --git a/testsuite/tests/ghci/scripts/T7873.script b/testsuite/tests/ghci/scripts/T7873.script index 404c1f5bda..1a358a478e 100644 --- a/testsuite/tests/ghci/scripts/T7873.script +++ b/testsuite/tests/ghci/scripts/T7873.script @@ -1,4 +1,4 @@ -:set -XPolyKinds -XRankNTypes -XGADTs -XTypeInType +:set -XPolyKinds -XRankNTypes -XGADTs data D1 = MkD1 (forall p (a :: k). p a -> Int) data D2 = MkD2 (forall p a. p a -> Int) data D3 = MkD3 (forall k p (a :: k). p a -> Int) diff --git a/testsuite/tests/ghci/scripts/T7939.hs b/testsuite/tests/ghci/scripts/T7939.hs index fbdf883b51..04a1f1a623 100644 --- a/testsuite/tests/ghci/scripts/T7939.hs +++ b/testsuite/tests/ghci/scripts/T7939.hs @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, TypeOperators #-} - module T7939 where +import Data.Kind (Type) class Foo a where type Bar a b @@ -22,6 +22,6 @@ type family K a where K '[] = Nothing K (h ': t) = Just h -type family L (a :: k) (b :: *) :: k where +type family L (a :: k) (b :: Type) :: k where L Int Int = Bool L Maybe Bool = IO diff --git a/testsuite/tests/ghci/scripts/T8357.hs b/testsuite/tests/ghci/scripts/T8357.hs index 82a34afdc6..322ec11e19 100644 --- a/testsuite/tests/ghci/scripts/T8357.hs +++ b/testsuite/tests/ghci/scripts/T8357.hs @@ -5,11 +5,12 @@ {-# LANGUAGE TypeOperators #-} module T8357 where +import Data.Kind (Type) import GHC.TypeLits data (:::) (sy :: Symbol) ty data Key (sy :: Symbol) -data Rec (rs :: [*]) +data Rec (rs :: [Type]) (*=) :: Key sy -> ty -> Rec '[sy ::: ty] (*=) = undefined @@ -17,7 +18,7 @@ data Rec (rs :: [*]) (.*.) :: (Union xs ys ~ rs) => Rec xs -> Rec ys -> Rec rs (.*.) = undefined -type family Union (xs :: [*]) (ys :: [*]) :: [*] where +type family Union (xs :: [Type]) (ys :: [Type]) :: [Type] where Union ((sy ::: t) ': xs) ys = (sy ::: t) ': Union xs ys Union '[] ys = ys @@ -30,4 +31,4 @@ fBar = undefined foo = fFoo *= "foo" bar = fBar *= "bar" -both = foo .*. bar
\ No newline at end of file +both = foo .*. bar |