summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_compile
diff options
context:
space:
mode:
authorVladislav Zavialov <vlad.z.4096@gmail.com>2018-06-14 15:02:36 -0400
committerRichard Eisenberg <rae@cs.brynmawr.edu>2018-06-14 15:05:32 -0400
commitd650729f9a0f3b6aa5e6ef2d5fba337f6f70fa60 (patch)
treeac224609397d4b7ca7072fc87739d2522be7675b /testsuite/tests/typecheck/should_compile
parent4672e2ebf040feffde4e7e2d79c479e4c0c3efaf (diff)
downloadhaskell-d650729f9a0f3b6aa5e6ef2d5fba337f6f70fa60.tar.gz
Embrace -XTypeInType, add -XStarIsType
Summary: Implement the "Embrace Type :: Type" GHC proposal, .../ghc-proposals/blob/master/proposals/0020-no-type-in-type.rst GHC 8.0 included a major change to GHC's type system: the Type :: Type axiom. Though casual users were protected from this by hiding its features behind the -XTypeInType extension, all programs written in GHC 8+ have the axiom behind the scenes. In order to preserve backward compatibility, various legacy features were left unchanged. For example, with -XDataKinds but not -XTypeInType, GADTs could not be used in types. Now these restrictions are lifted and -XTypeInType becomes a redundant flag that will be eventually deprecated. * Incorporate the features currently in -XTypeInType into the -XPolyKinds and -XDataKinds extensions. * Introduce a new extension -XStarIsType to control how to parse * in code and whether to print it in error messages. Test Plan: Validate Reviewers: goldfire, hvr, bgamari, alanz, simonpj Reviewed By: goldfire, simonpj Subscribers: rwbarton, thomie, mpickering, carter GHC Trac Issues: #15195 Differential Revision: https://phabricator.haskell.org/D4748
Diffstat (limited to 'testsuite/tests/typecheck/should_compile')
-rw-r--r--testsuite/tests/typecheck/should_compile/SplitWD.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T10432.hs5
-rw-r--r--testsuite/tests/typecheck/should_compile/T11237.hs4
-rw-r--r--testsuite/tests/typecheck/should_compile/T11348.hs1
-rw-r--r--testsuite/tests/typecheck/should_compile/T11524.hs1
-rw-r--r--testsuite/tests/typecheck/should_compile/T11723.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T11811.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T12133.hs6
-rw-r--r--testsuite/tests/typecheck/should_compile/T12381.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T12734.hs38
-rw-r--r--testsuite/tests/typecheck/should_compile/T12734a.hs31
-rw-r--r--testsuite/tests/typecheck/should_compile/T12734a.stderr9
-rw-r--r--testsuite/tests/typecheck/should_compile/T12785a.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T12911.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T12919.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T12987.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13083.hs5
-rw-r--r--testsuite/tests/typecheck/should_compile/T13333.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13337.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13343.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13458.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13603.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13643.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13822.hs3
-rw-r--r--testsuite/tests/typecheck/should_compile/T13871.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13879.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13915a.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13915b.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T13943.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T14441.hs3
-rw-r--r--testsuite/tests/typecheck/should_compile/T14934a.hs3
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T4
-rw-r--r--testsuite/tests/typecheck/should_compile/tc191.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/tc205.hs4
-rw-r--r--testsuite/tests/typecheck/should_compile/tc269.hs3
-rw-r--r--testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.hs2
36 files changed, 87 insertions, 75 deletions
diff --git a/testsuite/tests/typecheck/should_compile/SplitWD.hs b/testsuite/tests/typecheck/should_compile/SplitWD.hs
index 370b077b6e..5281cdbf0e 100644
--- a/testsuite/tests/typecheck/should_compile/SplitWD.hs
+++ b/testsuite/tests/typecheck/should_compile/SplitWD.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ScopedTypeVariables, TypeInType, TypeOperators,
+{-# LANGUAGE ScopedTypeVariables, TypeOperators, DataKinds, PolyKinds,
TypeFamilies, GADTs, StandaloneDeriving #-}
module SplitWD where
diff --git a/testsuite/tests/typecheck/should_compile/T10432.hs b/testsuite/tests/typecheck/should_compile/T10432.hs
index 7a9821e6cf..ec46f17f14 100644
--- a/testsuite/tests/typecheck/should_compile/T10432.hs
+++ b/testsuite/tests/typecheck/should_compile/T10432.hs
@@ -2,15 +2,16 @@
DataKinds, RankNTypes, GADTs, TypeOperators #-}
module T10432 where
+import Data.Kind (Type)
import Data.Type.Equality
data WrappedType = forall a. WrapType a;
-matchReflK :: forall (a :: ka) (b :: kb) (r :: *).
+matchReflK :: forall (a :: ka) (b :: kb) (r :: Type).
('WrapType a :~: 'WrapType b) -> (('WrapType a ~ 'WrapType b) => r) -> r;
matchReflK Refl r = r;
-matchReflK2 :: forall (a :: ka) (b :: kb) (r :: *).
+matchReflK2 :: forall (a :: ka) (b :: kb) (r :: Type).
('WrapType a :~: 'WrapType b) -> r
matchReflK2 x = let foo :: ('WrapType a ~ 'WrapType b) => r
foo = undefined
diff --git a/testsuite/tests/typecheck/should_compile/T11237.hs b/testsuite/tests/typecheck/should_compile/T11237.hs
index 422aefdb67..db15a7b337 100644
--- a/testsuite/tests/typecheck/should_compile/T11237.hs
+++ b/testsuite/tests/typecheck/should_compile/T11237.hs
@@ -1,6 +1,6 @@
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds, KindSignatures #-}
{-# LANGUAGE GADTs #-}
-module TypeInTypeBug where
+module T11237 where
import qualified Data.Kind
diff --git a/testsuite/tests/typecheck/should_compile/T11348.hs b/testsuite/tests/typecheck/should_compile/T11348.hs
index 2548dbdab7..6edc0acd3e 100644
--- a/testsuite/tests/typecheck/should_compile/T11348.hs
+++ b/testsuite/tests/typecheck/should_compile/T11348.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE TypeInType #-}
module T11348 where
diff --git a/testsuite/tests/typecheck/should_compile/T11524.hs b/testsuite/tests/typecheck/should_compile/T11524.hs
index d257554439..d6e2adf4f4 100644
--- a/testsuite/tests/typecheck/should_compile/T11524.hs
+++ b/testsuite/tests/typecheck/should_compile/T11524.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE PatternSynonyms #-}
-{-# LANGUAGE TypeInType #-}
module T11524 where
diff --git a/testsuite/tests/typecheck/should_compile/T11723.hs b/testsuite/tests/typecheck/should_compile/T11723.hs
index 1933024f2e..636e40fdb0 100644
--- a/testsuite/tests/typecheck/should_compile/T11723.hs
+++ b/testsuite/tests/typecheck/should_compile/T11723.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds, PolyKinds #-}
module Example where
import Data.Typeable
diff --git a/testsuite/tests/typecheck/should_compile/T11811.hs b/testsuite/tests/typecheck/should_compile/T11811.hs
index 16a225b4cf..a3fadb92e7 100644
--- a/testsuite/tests/typecheck/should_compile/T11811.hs
+++ b/testsuite/tests/typecheck/should_compile/T11811.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType, GADTs #-}
+{-# LANGUAGE PolyKinds, GADTs #-}
module T11811 where
diff --git a/testsuite/tests/typecheck/should_compile/T12133.hs b/testsuite/tests/typecheck/should_compile/T12133.hs
index f2502a786a..f35c51000d 100644
--- a/testsuite/tests/typecheck/should_compile/T12133.hs
+++ b/testsuite/tests/typecheck/should_compile/T12133.hs
@@ -11,10 +11,10 @@
module T12133 where
import GHC.Classes (IP(..))
-import GHC.Exts (Constraint)
+import Data.Kind (Constraint, Type)
-- | From "Data.Constraint":
-data Dict :: Constraint -> * where Dict :: a => Dict a
+data Dict :: Constraint -> Type where Dict :: a => Dict a
newtype a :- b = Sub (a => Dict b)
@@ -65,4 +65,4 @@ t.hs:44:13: error:
foo :: (c1, c2) :- c3 -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3)
(bound at t.hs:40:1)
Failed, modules loaded: none.
--} \ No newline at end of file
+-}
diff --git a/testsuite/tests/typecheck/should_compile/T12381.hs b/testsuite/tests/typecheck/should_compile/T12381.hs
index 9d4d731374..102a48321c 100644
--- a/testsuite/tests/typecheck/should_compile/T12381.hs
+++ b/testsuite/tests/typecheck/should_compile/T12381.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType, TypeFamilies #-}
+{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies #-}
module Kinds where
import GHC.Types
diff --git a/testsuite/tests/typecheck/should_compile/T12734.hs b/testsuite/tests/typecheck/should_compile/T12734.hs
index a3b26d5aaf..e88d21a233 100644
--- a/testsuite/tests/typecheck/should_compile/T12734.hs
+++ b/testsuite/tests/typecheck/should_compile/T12734.hs
@@ -20,6 +20,7 @@
module T12734 where
import Prelude
+import Data.Kind
import Control.Applicative
import Control.Monad.Fix
import Control.Monad.Trans.Identity
@@ -30,14 +31,14 @@ import Control.Monad.IO.Class
data A
data B
data Net
-data Type
+data Ty
data Layer4 t l
data TermStore
-- Helpers: Stack
-data Stack layers (t :: * -> *) where
+data Stack layers (t :: Type -> Type) where
SLayer :: t l -> Stack ls t -> Stack (l ': ls) t
SNull :: Stack '[] t
@@ -57,28 +58,35 @@ type TermStack t layers = Stack layers (Layer4 (Expr t layers))
class Monad m => Constructor m t
instance ( Monad m, expr ~ Expr t layers, Constructor m (TermStack t layers)
- ) => Constructor m (Layer4 expr Type)
+ ) => Constructor m (Layer4 expr Ty)
--- HERE IS A FUNNY BEHAVIOR: the commented line raises context reduction stack overflow
-test_gr :: ( Constructor m (TermStack t layers), Inferable A layers m, Inferable B t m
- , bind ~ Expr t layers
--- ) => m (Expr t layers)
- ) => m bind
+-- HERE IS A FUNNY BEHAVIOR: the commented line raises context reduction stack
+-- overflow
+test_gr ::
+ ( Constructor m (TermStack t layers), Inferable A layers m, Inferable B t m
+ , bind ~ Expr t layers
+-- ) => m (Expr t layers)
+ ) => m bind
test_gr = undefined
-- Explicit information about a type which could be inferred
-class Monad m => Inferable (cls :: *) (t :: k) m | cls m -> t
+class Monad m => Inferable (cls :: Type) (t :: k) m | cls m -> t
-newtype KnownTypex (cls :: *) (t :: k) (m :: * -> *) (a :: *) = KnownTypex (IdentityT m a) deriving (Show, Functor, Monad, MonadIO, MonadFix, MonadTrans, Applicative, Alternative)
+newtype KnownTyx (cls :: Type) (t :: k) (m :: Type -> Type) (a :: Type) =
+ KnownTyx (IdentityT m a)
+ deriving (Show, Functor, Monad, MonadIO, MonadFix, MonadTrans,
+ Applicative, Alternative)
-instance {-# OVERLAPPABLE #-} (t ~ t', Monad m) => Inferable cls t (KnownTypex cls t' m)
-instance {-# OVERLAPPABLE #-} (Inferable cls t n, MonadTrans m, Monad (m n)) => Inferable cls t (m n)
+instance {-# OVERLAPPABLE #-} (t ~ t', Monad m) =>
+ Inferable cls t (KnownTyx cls t' m)
+instance {-# OVERLAPPABLE #-} (Inferable cls t n, MonadTrans m, Monad (m n)) =>
+ Inferable cls t (m n)
-runInferenceTx :: forall cls t m a. KnownTypex cls t m a -> m a
+runInferenceTx :: forall cls t m a. KnownTyx cls t m a -> m a
runInferenceTx = undefined
@@ -86,7 +94,7 @@ runInferenceTx = undefined
-- running it
test_ghc_err :: (MonadIO m, MonadFix m)
- => m (Expr Net '[Type])
+ => m (Expr Net '[Ty])
test_ghc_err = runInferenceTx @B @Net
- $ runInferenceTx @A @'[Type]
+ $ runInferenceTx @A @'[Ty]
$ (test_gr)
diff --git a/testsuite/tests/typecheck/should_compile/T12734a.hs b/testsuite/tests/typecheck/should_compile/T12734a.hs
index 3add59e648..5f1da8b818 100644
--- a/testsuite/tests/typecheck/should_compile/T12734a.hs
+++ b/testsuite/tests/typecheck/should_compile/T12734a.hs
@@ -21,6 +21,7 @@
module T12734a where
import Prelude
+import Data.Kind
import Control.Applicative
import Control.Monad.Fix
import Control.Monad.Trans.Identity
@@ -31,12 +32,12 @@ import Control.Monad.IO.Class
data A
data B
data Net
-data Type
+data Ty
data Layer4 t l
data TermStore
-data Stack lrs (t :: * -> *) where
+data Stack lrs (t :: Type -> Type) where
SLayer :: t l -> Stack ls t -> Stack (l ': ls) t
SNull :: Stack '[] t
@@ -44,7 +45,7 @@ instance ( Con m (t l)
, Con m (Stack ls t)) => Con m (Stack (l ': ls) t)
instance Monad m => Con m (Stack '[] t)
instance ( expr ~ Expr t lrs
- , Con m (TStk t lrs)) => Con m (Layer4 expr Type)
+ , Con m (TStk t lrs)) => Con m (Layer4 expr Ty)
newtype Expr t lrs = Expr (TStk t lrs)
@@ -63,18 +64,18 @@ test_gr :: forall m t lrs bind.
test_gr = undefined
-newtype KT (cls :: *) (t :: k) (m :: * -> *) (a :: *)
+newtype KT (cls :: Type) (t :: k) (m :: Type -> Type) (a :: Type)
= KT (IdentityT m a)
-test_ghc_err :: KT A '[Type] IO (Expr Net '[Type])
+test_ghc_err :: KT A '[Ty] IO (Expr Net '[Ty])
-test_ghc_err = test_gr @(KT A '[Type] IO) @_ @'[Type] @(Expr Net '[Type])
+test_ghc_err = test_gr @(KT A '[Ty] IO) @_ @'[Ty] @(Expr Net '[Ty])
{- Works!
-test_ghc_err = test_gr @(KT A '[Type] IO)
+test_ghc_err = test_gr @(KT A '[Ty] IO)
@Net
- @'[Type]
- @(Expr Net '[Type])
+ @'[Ty]
+ @(Expr Net '[Ty])
-}
{- Some notes. See comment:10 on Trac #12734
@@ -82,22 +83,22 @@ test_ghc_err = test_gr @(KT A '[Type] IO)
[W] Con m (TStk t lrs)
[W] Inferable A lrs m
[W] bind ~ Expr t lrs
-[W] m bind ~ KT A '[Type] IO (Expr Net '[Type])
+[W] m bind ~ KT A '[Ty] IO (Expr Net '[Ty])
-==> m := KT A '[Type] IO
- bind := Expr Net '[Type]
+==> m := KT A '[Ty] IO
+ bind := Expr Net '[Ty]
t := Net
- lrs := '[Type]
+ lrs := '[Ty]
[W] Con m (TStk t lrs)
= Con m (Stack lrs (Layer4 bind))
--> inline lrs
-[W] Con m (Stack '[Type] (Layer4 bind))
+[W] Con m (Stack '[Ty] (Layer4 bind))
--> instance
[W] Con m (Stack '[] bind)
--> Monad m
+
-[W] Con m (Layer4 bind Type)
+[W] Con m (Layer4 bind Ty)
-->
[W] bind ~ Expr t0 lrs0
[W] Con m (TStk t0 lrs0)
diff --git a/testsuite/tests/typecheck/should_compile/T12734a.stderr b/testsuite/tests/typecheck/should_compile/T12734a.stderr
index 737659fa57..8d777c6616 100644
--- a/testsuite/tests/typecheck/should_compile/T12734a.stderr
+++ b/testsuite/tests/typecheck/should_compile/T12734a.stderr
@@ -1,9 +1,8 @@
-T12734a.hs:71:16: error:
- • No instance for (Monad (KT A '[Type] IO))
+T12734a.hs:72:16: error:
+ • No instance for (Monad (KT A '[Ty] IO))
arising from a use of ‘test_gr’
• In the expression:
- test_gr @(KT A '[Type] IO) @_ @'[Type] @(Expr Net '[Type])
+ test_gr @(KT A '[Ty] IO) @_ @'[Ty] @(Expr Net '[Ty])
In an equation for ‘test_ghc_err’:
- test_ghc_err
- = test_gr @(KT A '[Type] IO) @_ @'[Type] @(Expr Net '[Type])
+ test_ghc_err = test_gr @(KT A '[Ty] IO) @_ @'[Ty] @(Expr Net '[Ty])
diff --git a/testsuite/tests/typecheck/should_compile/T12785a.hs b/testsuite/tests/typecheck/should_compile/T12785a.hs
index 1e4d6a1b64..3c3fa9aba5 100644
--- a/testsuite/tests/typecheck/should_compile/T12785a.hs
+++ b/testsuite/tests/typecheck/should_compile/T12785a.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module T12785a where
diff --git a/testsuite/tests/typecheck/should_compile/T12911.hs b/testsuite/tests/typecheck/should_compile/T12911.hs
index 88c2125f2b..af3af3c5f3 100644
--- a/testsuite/tests/typecheck/should_compile/T12911.hs
+++ b/testsuite/tests/typecheck/should_compile/T12911.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ExplicitForAll, TypeInType, GADTSyntax,
+{-# LANGUAGE ExplicitForAll, PolyKinds, GADTSyntax,
ExistentialQuantification #-}
module T12911 where
diff --git a/testsuite/tests/typecheck/should_compile/T12919.hs b/testsuite/tests/typecheck/should_compile/T12919.hs
index 1f77c1c8de..778abfa1e7 100644
--- a/testsuite/tests/typecheck/should_compile/T12919.hs
+++ b/testsuite/tests/typecheck/should_compile/T12919.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType, TypeFamilies, GADTs, ConstraintKinds #-}
+{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, GADTs, ConstraintKinds #-}
module T12919 where
diff --git a/testsuite/tests/typecheck/should_compile/T12987.hs b/testsuite/tests/typecheck/should_compile/T12987.hs
index 0997985601..3341272df9 100644
--- a/testsuite/tests/typecheck/should_compile/T12987.hs
+++ b/testsuite/tests/typecheck/should_compile/T12987.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
module T12987 where
diff --git a/testsuite/tests/typecheck/should_compile/T13083.hs b/testsuite/tests/typecheck/should_compile/T13083.hs
index 220da0855a..e294052309 100644
--- a/testsuite/tests/typecheck/should_compile/T13083.hs
+++ b/testsuite/tests/typecheck/should_compile/T13083.hs
@@ -8,11 +8,12 @@
module T13083 where
+import Data.Kind
import GHC.Generics (Par1(..),(:*:)(..))
import GHC.Exts (coerce)
-- Representation as free vector space
-type family V (a :: *) :: * -> *
+type family V (a :: Type) :: Type -> Type
type instance V R = Par1
type instance V (a,b) = V a :*: V b
@@ -59,7 +60,7 @@ foo = coerce
-- with that of ‘Par1’
-- arising from a use of ‘coerce’
--- Note that Par1 has the wrong kind (* -> *) for V Par1
+-- Note that Par1 has the wrong kind (Type -> Type) for V Par1
-- Same error:
--
diff --git a/testsuite/tests/typecheck/should_compile/T13333.hs b/testsuite/tests/typecheck/should_compile/T13333.hs
index fba64cede0..5aca099c3b 100644
--- a/testsuite/tests/typecheck/should_compile/T13333.hs
+++ b/testsuite/tests/typecheck/should_compile/T13333.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
module T13333 where
diff --git a/testsuite/tests/typecheck/should_compile/T13337.hs b/testsuite/tests/typecheck/should_compile/T13337.hs
index 39808b4f13..3448d9448a 100644
--- a/testsuite/tests/typecheck/should_compile/T13337.hs
+++ b/testsuite/tests/typecheck/should_compile/T13337.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType, ScopedTypeVariables, TypeOperators, GADTs #-}
+{-# LANGUAGE PolyKinds, ScopedTypeVariables, TypeOperators, GADTs #-}
{-# OPTIONS_GHC -Wno-overlapping-patterns #-} -- don't want erroneous warning in test output
-- if removing this doesn't change output, then
-- remove it!
diff --git a/testsuite/tests/typecheck/should_compile/T13343.hs b/testsuite/tests/typecheck/should_compile/T13343.hs
index a00655d5ef..fcff9db1a4 100644
--- a/testsuite/tests/typecheck/should_compile/T13343.hs
+++ b/testsuite/tests/typecheck/should_compile/T13343.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
module Bug where
import GHC.Exts
diff --git a/testsuite/tests/typecheck/should_compile/T13458.hs b/testsuite/tests/typecheck/should_compile/T13458.hs
index 9b51378d65..ef1f568769 100644
--- a/testsuite/tests/typecheck/should_compile/T13458.hs
+++ b/testsuite/tests/typecheck/should_compile/T13458.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash, TypeInType, ScopedTypeVariables #-}
+{-# LANGUAGE MagicHash, PolyKinds, ScopedTypeVariables #-}
{-# OPTIONS_GHC -O #-}
module T13458 where
import GHC.Exts
diff --git a/testsuite/tests/typecheck/should_compile/T13603.hs b/testsuite/tests/typecheck/should_compile/T13603.hs
index d0c1975e04..bcbed465b0 100644
--- a/testsuite/tests/typecheck/should_compile/T13603.hs
+++ b/testsuite/tests/typecheck/should_compile/T13603.hs
@@ -1,4 +1,4 @@
-{-# Language PolyKinds, TypeInType, UndecidableInstances #-}
+{-# Language PolyKinds, UndecidableInstances #-}
module T13603 where
import GHC.Exts (TYPE, RuntimeRep)
diff --git a/testsuite/tests/typecheck/should_compile/T13643.hs b/testsuite/tests/typecheck/should_compile/T13643.hs
index d7cf1342c8..68e7225bf8 100644
--- a/testsuite/tests/typecheck/should_compile/T13643.hs
+++ b/testsuite/tests/typecheck/should_compile/T13643.hs
@@ -2,7 +2,7 @@
{-# Language RankNTypes #-}
{-# Language KindSignatures #-}
{-# Language DataKinds #-}
-{-# Language TypeInType #-}
+{-# Language PolyKinds #-}
{-# Language GADTs #-}
import Data.Kind (Type)
diff --git a/testsuite/tests/typecheck/should_compile/T13822.hs b/testsuite/tests/typecheck/should_compile/T13822.hs
index 5837cc8081..88c14c2aff 100644
--- a/testsuite/tests/typecheck/should_compile/T13822.hs
+++ b/testsuite/tests/typecheck/should_compile/T13822.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE GADTs, TypeOperators, PolyKinds, DataKinds, TypeFamilyDependencies, TypeInType, RankNTypes, LambdaCase, EmptyCase #-}
+{-# LANGUAGE GADTs, TypeOperators, PolyKinds, DataKinds,
+ TypeFamilyDependencies, RankNTypes, LambdaCase, EmptyCase #-}
module T13822 where
diff --git a/testsuite/tests/typecheck/should_compile/T13871.hs b/testsuite/tests/typecheck/should_compile/T13871.hs
index 319d949647..623923eaca 100644
--- a/testsuite/tests/typecheck/should_compile/T13871.hs
+++ b/testsuite/tests/typecheck/should_compile/T13871.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds, PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
module Foo where
diff --git a/testsuite/tests/typecheck/should_compile/T13879.hs b/testsuite/tests/typecheck/should_compile/T13879.hs
index 9708c1dd41..2e10c472fb 100644
--- a/testsuite/tests/typecheck/should_compile/T13879.hs
+++ b/testsuite/tests/typecheck/should_compile/T13879.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds, PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
module Bug where
diff --git a/testsuite/tests/typecheck/should_compile/T13915a.hs b/testsuite/tests/typecheck/should_compile/T13915a.hs
index 484c9dedc0..355166b8a0 100644
--- a/testsuite/tests/typecheck/should_compile/T13915a.hs
+++ b/testsuite/tests/typecheck/should_compile/T13915a.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds, PolyKinds #-}
module Bug where
import T13915a_Foo
diff --git a/testsuite/tests/typecheck/should_compile/T13915b.hs b/testsuite/tests/typecheck/should_compile/T13915b.hs
index dd64b13d4f..8949a86f06 100644
--- a/testsuite/tests/typecheck/should_compile/T13915b.hs
+++ b/testsuite/tests/typecheck/should_compile/T13915b.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds #-}
module Foo where
import Data.Typeable (Proxy(..), typeRep)
diff --git a/testsuite/tests/typecheck/should_compile/T13943.hs b/testsuite/tests/typecheck/should_compile/T13943.hs
index f40ee237e6..7889fe6a41 100644
--- a/testsuite/tests/typecheck/should_compile/T13943.hs
+++ b/testsuite/tests/typecheck/should_compile/T13943.hs
@@ -5,7 +5,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds, DataKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE GADTs #-}
diff --git a/testsuite/tests/typecheck/should_compile/T14441.hs b/testsuite/tests/typecheck/should_compile/T14441.hs
index 047de1659f..a2c1aff9ef 100644
--- a/testsuite/tests/typecheck/should_compile/T14441.hs
+++ b/testsuite/tests/typecheck/should_compile/T14441.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
module T14441 where
import Data.Kind
diff --git a/testsuite/tests/typecheck/should_compile/T14934a.hs b/testsuite/tests/typecheck/should_compile/T14934a.hs
index 3ba59ff976..3a4865fffc 100644
--- a/testsuite/tests/typecheck/should_compile/T14934a.hs
+++ b/testsuite/tests/typecheck/should_compile/T14934a.hs
@@ -4,9 +4,10 @@
{-# LANGUAGE TypeOperators #-}
module T14934a where
+import Data.Kind (Type)
import GHC.TypeLits
-data Foo :: Nat -> * where
+data Foo :: Nat -> Type where
MkFoo0 :: Foo 0
MkFoo1 :: Foo 1
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index f566182cc2..8a7a7da8ce 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -579,8 +579,8 @@ test('T13848', normal, compile, [''])
test('T13871', normal, compile, [''])
test('T13879', normal, compile, [''])
test('T13881', normal, compile, [''])
-test('T13915a', normal, multimod_compile, ['T13915a', '-v0'])
-test('T13915b', normal, compile, [''])
+test('T13915a', expect_broken(15245), multimod_compile, ['T13915a', '-v0'])
+test('T13915b', expect_broken(15245), compile, [''])
test('T13984', normal, compile, [''])
test('T14128', normal, multimod_compile, ['T14128Main', '-v0'])
test('T14149', normal, compile_fail, [''])
diff --git a/testsuite/tests/typecheck/should_compile/tc191.hs b/testsuite/tests/typecheck/should_compile/tc191.hs
index 403ec88da9..c7a7c3e4c6 100644
--- a/testsuite/tests/typecheck/should_compile/tc191.hs
+++ b/testsuite/tests/typecheck/should_compile/tc191.hs
@@ -1,4 +1,4 @@
-
+{-# LANGUAGE RankNTypes #-}
-- This only typechecks if forall-hoisting works ok when
-- importing from an interface file. The type of Twins.gzipWithQ
diff --git a/testsuite/tests/typecheck/should_compile/tc205.hs b/testsuite/tests/typecheck/should_compile/tc205.hs
index 1fe2cc255f..e45660fb3a 100644
--- a/testsuite/tests/typecheck/should_compile/tc205.hs
+++ b/testsuite/tests/typecheck/should_compile/tc205.hs
@@ -4,7 +4,9 @@
module ShouldCompile where
+import Data.Kind
+
infix 1 `DArrowX` -- (->) has precedence 0
-data DArrowX :: * -> * -> * where
+data DArrowX :: Type -> Type -> Type where
First :: a `DArrowX` a' -> (a,b) `DArrowX` (a',b)
diff --git a/testsuite/tests/typecheck/should_compile/tc269.hs b/testsuite/tests/typecheck/should_compile/tc269.hs
index 33151cebe8..3ac88ce8e9 100644
--- a/testsuite/tests/typecheck/should_compile/tc269.hs
+++ b/testsuite/tests/typecheck/should_compile/tc269.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE KindSignatures #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
module Tc269 where
import GHC.Types
diff --git a/testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.hs b/testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.hs
index a2186e73a3..069e1f7384 100644
--- a/testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.hs
+++ b/testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE GADTs #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
module ValidSubsInteractions where