summaryrefslogtreecommitdiff
path: root/testsuite/tests/dependent/should_fail
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/dependent/should_fail')
-rw-r--r--testsuite/tests/dependent/should_fail/T13895.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T13895.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T14845_fail1.hs2
-rw-r--r--testsuite/tests/dependent/should_fail/T14845_fail2.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T14845_fail2.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T14880-2.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T14880-2.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T14880.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T14880.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T15076.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T15076.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T15076b.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T15076b.stderr7
-rw-r--r--testsuite/tests/dependent/should_fail/T15215.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T15215.stderr4
-rw-r--r--testsuite/tests/dependent/should_fail/T15308.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T15308.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T15343.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T15343.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T15380.hs3
-rw-r--r--testsuite/tests/dependent/should_fail/T15380.stderr2
-rw-r--r--testsuite/tests/dependent/should_fail/T16344.hs2
-rw-r--r--testsuite/tests/dependent/should_fail/T16344a.hs2
-rw-r--r--testsuite/tests/dependent/should_fail/T17131.hs2
24 files changed, 37 insertions, 28 deletions
diff --git a/testsuite/tests/dependent/should_fail/T13895.hs b/testsuite/tests/dependent/should_fail/T13895.hs
index 5897cd8149..691290df8e 100644
--- a/testsuite/tests/dependent/should_fail/T13895.hs
+++ b/testsuite/tests/dependent/should_fail/T13895.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
module T13895 where
import Data.Data (Data, Typeable)
diff --git a/testsuite/tests/dependent/should_fail/T13895.stderr b/testsuite/tests/dependent/should_fail/T13895.stderr
index adfebdd113..5ab651fe0b 100644
--- a/testsuite/tests/dependent/should_fail/T13895.stderr
+++ b/testsuite/tests/dependent/should_fail/T13895.stderr
@@ -1,5 +1,5 @@
-T13895.hs:10:14: error:
+T13895.hs:11:14: error:
• Illegal constraint in a kind: forall k. Typeable k => k -> *
• In the type signature:
dataCast1 :: forall (a :: Type).
diff --git a/testsuite/tests/dependent/should_fail/T14845_fail1.hs b/testsuite/tests/dependent/should_fail/T14845_fail1.hs
index 46c1351027..f709c763a7 100644
--- a/testsuite/tests/dependent/should_fail/T14845_fail1.hs
+++ b/testsuite/tests/dependent/should_fail/T14845_fail1.hs
@@ -1,4 +1,4 @@
-{-# Language PolyKinds, DataKinds, KindSignatures, GADTs, TypeInType, ConstraintKinds #-}
+{-# Language PolyKinds, DataKinds, KindSignatures, GADTs, ConstraintKinds #-}
module T14845_fail1 where
import Data.Kind
diff --git a/testsuite/tests/dependent/should_fail/T14845_fail2.hs b/testsuite/tests/dependent/should_fail/T14845_fail2.hs
index 4c5dac730f..66d026cbed 100644
--- a/testsuite/tests/dependent/should_fail/T14845_fail2.hs
+++ b/testsuite/tests/dependent/should_fail/T14845_fail2.hs
@@ -1,7 +1,8 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
module T14845_fail2 where
import Data.Coerce
diff --git a/testsuite/tests/dependent/should_fail/T14845_fail2.stderr b/testsuite/tests/dependent/should_fail/T14845_fail2.stderr
index 9fe733f374..55519c582a 100644
--- a/testsuite/tests/dependent/should_fail/T14845_fail2.stderr
+++ b/testsuite/tests/dependent/should_fail/T14845_fail2.stderr
@@ -1,5 +1,5 @@
-T14845_fail2.hs:14:14: error:
+T14845_fail2.hs:15:14: error:
• Data constructor ‘MkA’ cannot be used here
(it has an unpromotable context ‘Coercible a Int’)
• In the first argument of ‘SA’, namely ‘MkA’
diff --git a/testsuite/tests/dependent/should_fail/T14880-2.hs b/testsuite/tests/dependent/should_fail/T14880-2.hs
index e7057a3f00..d1b4e48445 100644
--- a/testsuite/tests/dependent/should_fail/T14880-2.hs
+++ b/testsuite/tests/dependent/should_fail/T14880-2.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PartialTypeSignatures #-}
module Bug where
diff --git a/testsuite/tests/dependent/should_fail/T14880-2.stderr b/testsuite/tests/dependent/should_fail/T14880-2.stderr
index 2082ca6c34..56d8ff68ba 100644
--- a/testsuite/tests/dependent/should_fail/T14880-2.stderr
+++ b/testsuite/tests/dependent/should_fail/T14880-2.stderr
@@ -1,5 +1,5 @@
-T14880-2.hs:12:9: error:
+T14880-2.hs:13:9: error:
• Cannot generalise type; skolem ‘arg’ would escape its scope
if I tried to quantify (a0 :: arg) in this type:
forall arg. Proxy @{Proxy @{arg} a0 -> *} (Foo arg @a0) -> ()
diff --git a/testsuite/tests/dependent/should_fail/T14880.hs b/testsuite/tests/dependent/should_fail/T14880.hs
index 91cfb20a4a..e52c6dbaae 100644
--- a/testsuite/tests/dependent/should_fail/T14880.hs
+++ b/testsuite/tests/dependent/should_fail/T14880.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
module Bug where
import Data.Kind
diff --git a/testsuite/tests/dependent/should_fail/T14880.stderr b/testsuite/tests/dependent/should_fail/T14880.stderr
index a5aa1df8d2..90e54427c0 100644
--- a/testsuite/tests/dependent/should_fail/T14880.stderr
+++ b/testsuite/tests/dependent/should_fail/T14880.stderr
@@ -1,5 +1,5 @@
-T14880.hs:12:5: error:
+T14880.hs:13:5: error:
• Cannot generalise type; skolem ‘arg’ would escape its scope
if I tried to quantify (a0 :: arg) in this type:
forall x arg.
diff --git a/testsuite/tests/dependent/should_fail/T15076.hs b/testsuite/tests/dependent/should_fail/T15076.hs
index 0890cf9eab..dfd944dd39 100644
--- a/testsuite/tests/dependent/should_fail/T15076.hs
+++ b/testsuite/tests/dependent/should_fail/T15076.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PartialTypeSignatures #-}
module Bug where
diff --git a/testsuite/tests/dependent/should_fail/T15076.stderr b/testsuite/tests/dependent/should_fail/T15076.stderr
index 814d459c3c..71d3c7c156 100644
--- a/testsuite/tests/dependent/should_fail/T15076.stderr
+++ b/testsuite/tests/dependent/should_fail/T15076.stderr
@@ -1,5 +1,5 @@
-T15076.hs:10:8: error:
+T15076.hs:11:8: error:
• Cannot generalise type; skolem ‘a’ would escape its scope
if I tried to quantify (x0 :: a) in this type:
forall a (f :: forall (x :: a). Proxy @{a} x -> *).
diff --git a/testsuite/tests/dependent/should_fail/T15076b.hs b/testsuite/tests/dependent/should_fail/T15076b.hs
index 15fce826c0..5a69d5cc89 100644
--- a/testsuite/tests/dependent/should_fail/T15076b.hs
+++ b/testsuite/tests/dependent/should_fail/T15076b.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
module Bug where
import Data.Kind
diff --git a/testsuite/tests/dependent/should_fail/T15076b.stderr b/testsuite/tests/dependent/should_fail/T15076b.stderr
index 3ee27a82b3..8da932a044 100644
--- a/testsuite/tests/dependent/should_fail/T15076b.stderr
+++ b/testsuite/tests/dependent/should_fail/T15076b.stderr
@@ -1,5 +1,4 @@
-
-T15076b.hs:8:8: error:
+T15076b.hs:9:8: error:
• Cannot generalise type; skolem ‘a’ would escape its scope
if I tried to quantify (x0 :: a) in this type:
forall a (f :: forall (x :: a). Proxy @{a} x -> *).
@@ -7,5 +6,5 @@ T15076b.hs:8:8: error:
(Indeed, I sometimes struggle even printing this correctly,
due to its ill-scoped nature.)
• In the type signature:
- foo :: forall (a :: Type) (f :: forall (x :: a). Proxy x -> Type).
- Proxy f -> ()
+ foo :: forall (a :: Type)
+ (f :: forall (x :: a). Proxy x -> Type). Proxy f -> ()
diff --git a/testsuite/tests/dependent/should_fail/T15215.hs b/testsuite/tests/dependent/should_fail/T15215.hs
index 98b5e841b8..1b9708c33b 100644
--- a/testsuite/tests/dependent/should_fail/T15215.hs
+++ b/testsuite/tests/dependent/should_fail/T15215.hs
@@ -1,7 +1,8 @@
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
module T15215 where
import Data.Kind
diff --git a/testsuite/tests/dependent/should_fail/T15215.stderr b/testsuite/tests/dependent/should_fail/T15215.stderr
index e022054fa9..51119c1e7a 100644
--- a/testsuite/tests/dependent/should_fail/T15215.stderr
+++ b/testsuite/tests/dependent/should_fail/T15215.stderr
@@ -1,11 +1,11 @@
-T15215.hs:10:3: error:
+T15215.hs:11:3: error:
• Non type-variable argument in the constraint: Show (Maybe a)
• In the definition of data constructor ‘MkA’
In the data type declaration for ‘A’
Suggested fix: Perhaps you intended to use FlexibleContexts
-T15215.hs:17:14: error:
+T15215.hs:18:14: error:
• Data constructor ‘MkB’ cannot be used here
(it has an unpromotable context ‘Show a’)
• In the first argument of ‘SA’, namely ‘MkB’
diff --git a/testsuite/tests/dependent/should_fail/T15308.hs b/testsuite/tests/dependent/should_fail/T15308.hs
index b49fe1f75b..e0a41da8e8 100644
--- a/testsuite/tests/dependent/should_fail/T15308.hs
+++ b/testsuite/tests/dependent/should_fail/T15308.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
module T15308 where
import Data.Kind
diff --git a/testsuite/tests/dependent/should_fail/T15308.stderr b/testsuite/tests/dependent/should_fail/T15308.stderr
index a4bdbd5ab6..fdb019efc1 100644
--- a/testsuite/tests/dependent/should_fail/T15308.stderr
+++ b/testsuite/tests/dependent/should_fail/T15308.stderr
@@ -1,5 +1,5 @@
-T15308.hs:12:5: error:
+T15308.hs:13:5: error:
• No instance for (Show (Foo a f)) arising from a use of ‘show’
• In the expression: show
In an equation for ‘f’: f = show
diff --git a/testsuite/tests/dependent/should_fail/T15343.hs b/testsuite/tests/dependent/should_fail/T15343.hs
index 9bb59c807a..91b9b5bd2f 100644
--- a/testsuite/tests/dependent/should_fail/T15343.hs
+++ b/testsuite/tests/dependent/should_fail/T15343.hs
@@ -1,7 +1,8 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
module T15343 where
import Data.Kind
diff --git a/testsuite/tests/dependent/should_fail/T15343.stderr b/testsuite/tests/dependent/should_fail/T15343.stderr
index 79d81e5772..d3067812d2 100644
--- a/testsuite/tests/dependent/should_fail/T15343.stderr
+++ b/testsuite/tests/dependent/should_fail/T15343.stderr
@@ -1,5 +1,5 @@
-T15343.hs:14:18: error:
+T15343.hs:15:18: error:
• Expecting one more argument to ‘WhySym’
Expected kind ‘forall z. z’, but ‘WhySym’ has kind ‘* -> *’
• In the type ‘WhySym’
diff --git a/testsuite/tests/dependent/should_fail/T15380.hs b/testsuite/tests/dependent/should_fail/T15380.hs
index a0e8abc819..ac81e5532b 100644
--- a/testsuite/tests/dependent/should_fail/T15380.hs
+++ b/testsuite/tests/dependent/should_fail/T15380.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module T15380 where
diff --git a/testsuite/tests/dependent/should_fail/T15380.stderr b/testsuite/tests/dependent/should_fail/T15380.stderr
index 405d572c73..bf0355b01b 100644
--- a/testsuite/tests/dependent/should_fail/T15380.stderr
+++ b/testsuite/tests/dependent/should_fail/T15380.stderr
@@ -1,5 +1,5 @@
-T15380.hs:17:16: error:
+T15380.hs:18:16: error:
• Expecting one more argument to ‘To (M x)’
Expected a type, but ‘To (M x)’ has kind ‘Rep (M x) -> M x’
• In the type ‘To (M x)’
diff --git a/testsuite/tests/dependent/should_fail/T16344.hs b/testsuite/tests/dependent/should_fail/T16344.hs
index 0cf4b98642..dcc1e0b619 100644
--- a/testsuite/tests/dependent/should_fail/T16344.hs
+++ b/testsuite/tests/dependent/should_fail/T16344.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType, KindSignatures #-}
+{-# LANGUAGE PolyKinds, DataKinds, KindSignatures #-}
module T16344 where
diff --git a/testsuite/tests/dependent/should_fail/T16344a.hs b/testsuite/tests/dependent/should_fail/T16344a.hs
index cfc3091a04..989352eb3d 100644
--- a/testsuite/tests/dependent/should_fail/T16344a.hs
+++ b/testsuite/tests/dependent/should_fail/T16344a.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE TypeInType, KindSignatures #-}
+{-# LANGUAGE DataKinds, PolyKinds, KindSignatures #-}
module T16344 where
diff --git a/testsuite/tests/dependent/should_fail/T17131.hs b/testsuite/tests/dependent/should_fail/T17131.hs
index d4294c0216..b0617f354d 100644
--- a/testsuite/tests/dependent/should_fail/T17131.hs
+++ b/testsuite/tests/dependent/should_fail/T17131.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MagicHash, UnboxedTuples, TypeInType, TypeFamilies, TypeOperators #-}
+{-# LANGUAGE MagicHash, UnboxedTuples,PolyKinds, DataKinds, TypeFamilies, TypeOperators #-}
module T17131 where