summaryrefslogtreecommitdiff
path: root/testsuite/tests/ghci
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/ghci')
-rw-r--r--testsuite/tests/ghci/scripts/GhciKinds.hs4
-rw-r--r--testsuite/tests/ghci/scripts/T12550.script1
-rw-r--r--testsuite/tests/ghci/scripts/T4175.hs4
-rw-r--r--testsuite/tests/ghci/scripts/T4175.stdout10
-rw-r--r--testsuite/tests/ghci/scripts/T5417.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/T5417a.hs4
-rw-r--r--testsuite/tests/ghci/scripts/T6018ghcifail.script4
-rw-r--r--testsuite/tests/ghci/scripts/T9293.stdout20
-rw-r--r--testsuite/tests/ghci/scripts/TypeAppData.script4
-rw-r--r--testsuite/tests/ghci/scripts/TypeAppData.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/ghci024.stdout5
-rw-r--r--testsuite/tests/ghci/scripts/ghci050.script3
-rw-r--r--testsuite/tests/ghci/scripts/ghci050.stderr11
-rw-r--r--testsuite/tests/ghci/scripts/ghci057.stdout20
14 files changed, 72 insertions, 21 deletions
diff --git a/testsuite/tests/ghci/scripts/GhciKinds.hs b/testsuite/tests/ghci/scripts/GhciKinds.hs
index 8e1af372ee..2b60c8c106 100644
--- a/testsuite/tests/ghci/scripts/GhciKinds.hs
+++ b/testsuite/tests/ghci/scripts/GhciKinds.hs
@@ -1,7 +1,9 @@
{-# LANGUAGE TypeFamilies #-}
module GhciKinds where
-type family F a :: *
+import Data.Kind (Type)
+
+type family F a :: Type
type instance F [a] = a -> F a
type instance F Int = Bool
diff --git a/testsuite/tests/ghci/scripts/T12550.script b/testsuite/tests/ghci/scripts/T12550.script
index 7c07e8f1dd..2834aeb7d9 100644
--- a/testsuite/tests/ghci/scripts/T12550.script
+++ b/testsuite/tests/ghci/scripts/T12550.script
@@ -1,4 +1,5 @@
:set -fprint-explicit-foralls -XKindSignatures -XExplicitNamespaces -XUnicodeSyntax
+:set -Wno-star-is-type
import Data.Kind (type Type)
diff --git a/testsuite/tests/ghci/scripts/T4175.hs b/testsuite/tests/ghci/scripts/T4175.hs
index 0fc53e76e9..ef34a4891d 100644
--- a/testsuite/tests/ghci/scripts/T4175.hs
+++ b/testsuite/tests/ghci/scripts/T4175.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE ConstraintKinds #-}
module T4175 where
-import GHC.Exts
+import Data.Kind
type family A a b
type instance A Int Int = ()
@@ -30,5 +30,5 @@ class Z a
class F (a :: Constraint)
instance F (Z a)
-class G (a :: * -> *)
+class G (a :: Type -> Type)
instance G B
diff --git a/testsuite/tests/ghci/scripts/T4175.stdout b/testsuite/tests/ghci/scripts/T4175.stdout
index 75d6c27506..e95d9c76af 100644
--- a/testsuite/tests/ghci/scripts/T4175.stdout
+++ b/testsuite/tests/ghci/scripts/T4175.stdout
@@ -3,7 +3,7 @@ type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15
type instance A Int Int = () -- Defined at T4175.hs:8:15
type instance A (B a) b = () -- Defined at T4175.hs:10:15
data family B a -- Defined at T4175.hs:12:1
-instance G B -- Defined at T4175.hs:34:10
+instance [safe] G B -- Defined at T4175.hs:34:10
type instance A (B a) b = () -- Defined at T4175.hs:10:15
data instance B () = MkB -- Defined at T4175.hs:13:15
class C a where
@@ -17,7 +17,7 @@ type family E a :: *
E Int = String
-- Defined at T4175.hs:24:1
data () = () -- Defined in ‘GHC.Tuple’
-instance C () -- Defined at T4175.hs:21:10
+instance [safe] C () -- Defined at T4175.hs:21:10
instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’
instance Ord () -- Defined in ‘GHC.Classes’
@@ -43,8 +43,8 @@ instance Read a => Read (Maybe a) -- Defined in ‘GHC.Read’
instance Foldable Maybe -- Defined in ‘Data.Foldable’
instance Traversable Maybe -- Defined in ‘Data.Traversable’
type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15
-data Int = I# Int# -- Defined in ‘GHC.Types’
-instance C Int -- Defined at T4175.hs:18:10
+data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’
+instance [safe] C Int -- Defined at T4175.hs:18:10
instance Eq Int -- Defined in ‘GHC.Classes’
instance Ord Int -- Defined in ‘GHC.Classes’
instance Show Int -- Defined in ‘GHC.Show’
@@ -57,4 +57,4 @@ instance Integral Int -- Defined in ‘GHC.Real’
type instance D Int () = String -- Defined at T4175.hs:19:10
type instance A Int Int = () -- Defined at T4175.hs:8:15
class Z a -- Defined at T4175.hs:28:1
-instance F (Z a) -- Defined at T4175.hs:31:10
+instance [safe] F (Z a) -- Defined at T4175.hs:31:10
diff --git a/testsuite/tests/ghci/scripts/T5417.stdout b/testsuite/tests/ghci/scripts/T5417.stdout
index 30178a44ab..ab2827730f 100644
--- a/testsuite/tests/ghci/scripts/T5417.stdout
+++ b/testsuite/tests/ghci/scripts/T5417.stdout
@@ -5,5 +5,5 @@ class C.C1 a where
data family C.F a
class C.C1 a where
data family C.F a
- -- Defined at T5417a.hs:5:5
+ -- Defined at T5417a.hs:7:5
data instance C.F (B1 a) = B2 a -- Defined at T5417.hs:8:10
diff --git a/testsuite/tests/ghci/scripts/T5417a.hs b/testsuite/tests/ghci/scripts/T5417a.hs
index 8143023e9e..2663245c42 100644
--- a/testsuite/tests/ghci/scripts/T5417a.hs
+++ b/testsuite/tests/ghci/scripts/T5417a.hs
@@ -1,5 +1,7 @@
{-# LANGUAGE TypeFamilies #-}
module T5417a where
+ import Data.Kind (Type)
+
class C1 a where
- data F a :: *
+ data F a :: Type
diff --git a/testsuite/tests/ghci/scripts/T6018ghcifail.script b/testsuite/tests/ghci/scripts/T6018ghcifail.script
index 4a382307db..b8c38cbd58 100644
--- a/testsuite/tests/ghci/scripts/T6018ghcifail.script
+++ b/testsuite/tests/ghci/scripts/T6018ghcifail.script
@@ -2,10 +2,10 @@
:set -XDataKinds
:set -XUndecidableInstances
:set -XPolyKinds
+import Data.Kind (Type)
-
-type family F a b c = (result :: *) | result -> a b c
+type family F a b c = (result :: Type) | result -> a b c
type instance F Int Char Bool = Bool
type instance F Char Bool Int = Int
type instance F Bool Int Char = Int
diff --git a/testsuite/tests/ghci/scripts/T9293.stdout b/testsuite/tests/ghci/scripts/T9293.stdout
index 2e5adc404c..6d140bc9f7 100644
--- a/testsuite/tests/ghci/scripts/T9293.stdout
+++ b/testsuite/tests/ghci/scripts/T9293.stdout
@@ -13,6 +13,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should fail, GADTs is not enabled
options currently set: none.
base language is: Haskell2010
@@ -32,6 +37,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should work, GADTs is in force from :set
options currently set: none.
base language is: Haskell2010
@@ -50,6 +60,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should fail, GADTs is now disabled
base language is: Haskell2010
with the following modifiers:
@@ -70,5 +85,10 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should fail, GADTs is only enabled at the prompt
C :: T Int
diff --git a/testsuite/tests/ghci/scripts/TypeAppData.script b/testsuite/tests/ghci/scripts/TypeAppData.script
index 9d571e11ac..f569473d23 100644
--- a/testsuite/tests/ghci/scripts/TypeAppData.script
+++ b/testsuite/tests/ghci/scripts/TypeAppData.script
@@ -16,7 +16,8 @@ data P6 = forall k (a :: k). P6 (P1 a)
pattern P7 :: P1 a ; pattern P7 = P1
pattern P8 :: forall a. P1 a ; pattern P8 = P1
pattern P9 :: forall k (a :: k). P1 a ; pattern P9 = P1
-pattern P10 :: forall (a :: k). P1 a ; pattern P10 = P1
+-- P10 commented out because implicit kind variables are no longer allowed
+-- pattern P10 :: forall (a :: k). P1 a ; pattern P10 = P1
pattern P11 :: () => P1 a -> P5 ; pattern P11 a = P5 a
pattern P12 :: () => forall a. P1 a -> P5 ; pattern P12 a = P5 a
pattern P13 :: () => forall k (a :: k). P1 a -> P5 ; pattern P13 a = P5 a
@@ -24,7 +25,6 @@ pattern P14 :: () => forall (a :: k). P1 a -> P5 ; pattern P14 a = P5 a
:type P7
:type P8
:type P9
-:type P10
:type P11
:type P12
:type P13
diff --git a/testsuite/tests/ghci/scripts/TypeAppData.stdout b/testsuite/tests/ghci/scripts/TypeAppData.stdout
index 0fd5506638..dd548c85da 100644
--- a/testsuite/tests/ghci/scripts/TypeAppData.stdout
+++ b/testsuite/tests/ghci/scripts/TypeAppData.stdout
@@ -7,7 +7,6 @@ P6 :: forall {k} {a :: k}. P1 a -> P6
P7 :: forall {k} {a :: k}. P1 a
P8 :: forall {k} {a :: k}. P1 a
P9 :: forall {k} {a :: k}. P1 a
-P10 :: forall {k} {a :: k}. P1 a
P11 :: forall {k} {a :: k}. P1 a -> P5
P12 :: forall {k} {a :: k}. P1 a -> P5
P13 :: forall {k} {a :: k}. P1 a -> P5
diff --git a/testsuite/tests/ghci/scripts/ghci024.stdout b/testsuite/tests/ghci/scripts/ghci024.stdout
index f38393bad4..863184ad49 100644
--- a/testsuite/tests/ghci/scripts/ghci024.stdout
+++ b/testsuite/tests/ghci/scripts/ghci024.stdout
@@ -14,6 +14,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
~~~~~~~~~~ Testing :set -a
options currently set: none.
base language is: Haskell2010
diff --git a/testsuite/tests/ghci/scripts/ghci050.script b/testsuite/tests/ghci/scripts/ghci050.script
index 277e803294..a463e153b4 100644
--- a/testsuite/tests/ghci/scripts/ghci050.script
+++ b/testsuite/tests/ghci/scripts/ghci050.script
@@ -1,7 +1,8 @@
--Testing for proper name printing in complex error messages (a previous bug)
:set -XTypeFamilies
:set -XFlexibleInstances
-class Listable t where ; type ListableElem t :: * ; asList :: t -> [ListableElem t]
+import Data.Kind (Type)
+class Listable t where ; type ListableElem t :: Type; asList :: t -> [ListableElem t]
instance Listable (a,a) where ; asList (a,b) = [a,b]
instance Listable (a,a) where ; type ListableElem (a,a) = a ; asList (a,b) = [a,b]
asList ("as","df")
diff --git a/testsuite/tests/ghci/scripts/ghci050.stderr b/testsuite/tests/ghci/scripts/ghci050.stderr
index a488269f73..25a0507199 100644
--- a/testsuite/tests/ghci/scripts/ghci050.stderr
+++ b/testsuite/tests/ghci/scripts/ghci050.stderr
@@ -1,14 +1,15 @@
-<interactive>:5:49: error:
+<interactive>:6:49: error:
• Couldn't match expected type ‘ListableElem (a, a)’
with actual type ‘a’
‘a’ is a rigid type variable bound by
- the instance declaration at <interactive>:5:10-23
+ the instance declaration
+ at <interactive>:6:10-23
• In the expression: a
In the expression: [a, b]
In an equation for ‘asList’: asList (a, b) = [a, b]
• Relevant bindings include
- b :: a (bound at <interactive>:5:43)
- a :: a (bound at <interactive>:5:41)
+ b :: a (bound at <interactive>:6:43)
+ a :: a (bound at <interactive>:6:41)
asList :: (a, a) -> [ListableElem (a, a)]
- (bound at <interactive>:5:33)
+ (bound at <interactive>:6:33)
diff --git a/testsuite/tests/ghci/scripts/ghci057.stdout b/testsuite/tests/ghci/scripts/ghci057.stdout
index 2e5adc404c..6d140bc9f7 100644
--- a/testsuite/tests/ghci/scripts/ghci057.stdout
+++ b/testsuite/tests/ghci/scripts/ghci057.stdout
@@ -13,6 +13,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should fail, GADTs is not enabled
options currently set: none.
base language is: Haskell2010
@@ -32,6 +37,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should work, GADTs is in force from :set
options currently set: none.
base language is: Haskell2010
@@ -50,6 +60,11 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should fail, GADTs is now disabled
base language is: Haskell2010
with the following modifiers:
@@ -70,5 +85,10 @@ other dynamic, non-language, flag settings:
-fimplicit-import-qualified
-fshow-warning-groups
warning settings:
+ -Wimplicit-kind-vars
+ -Wmissing-monadfail-instances
+ -Wsemigroup
+ -Wnoncanonical-monoid-instances
+ -Wstar-is-type
Should fail, GADTs is only enabled at the prompt
C :: T Int