summaryrefslogtreecommitdiff
path: root/testsuite/tests/ghci
diff options
context:
space:
mode:
authorVladislav Zavialov <vlad.z.4096@gmail.com>2019-03-29 10:18:03 +0300
committerVladislav Zavialov <vlad.z.4096@gmail.com>2019-09-25 21:06:04 +0300
commit0b5eede97804ec3dfbfa9df9f97bcfe2aa369f6b (patch)
treec6f6452ba5ae3a3d9f2986c79e054ea55a601884 /testsuite/tests/ghci
parent795986aaf33e2ffc233836b86a92a77366c91db2 (diff)
downloadhaskell-0b5eede97804ec3dfbfa9df9f97bcfe2aa369f6b.tar.gz
Standalone kind signatures (#16794)wip/top-level-kind-signatures
Implements GHC Proposal #54: .../ghc-proposals/blob/master/proposals/0054-kind-signatures.rst With this patch, a type constructor can now be given an explicit standalone kind signature: {-# LANGUAGE StandaloneKindSignatures #-} type Functor :: (Type -> Type) -> Constraint class Functor f where fmap :: (a -> b) -> f a -> f b This is a replacement for CUSKs (complete user-specified kind signatures), which are now scheduled for deprecation. User-facing changes ------------------- * A new extension flag has been added, -XStandaloneKindSignatures, which implies -XNoCUSKs. * There is a new syntactic construct, a standalone kind signature: type <name> :: <kind> Declarations of data types, classes, data families, type families, and type synonyms may be accompanied by a standalone kind signature. * A standalone kind signature enables polymorphic recursion in types, just like a function type signature enables polymorphic recursion in terms. This obviates the need for CUSKs. * TemplateHaskell AST has been extended with 'KiSigD' to represent standalone kind signatures. * GHCi :info command now prints the kind signature of type constructors: ghci> :info Functor type Functor :: (Type -> Type) -> Constraint ... Limitations ----------- * 'forall'-bound type variables of a standalone kind signature do not scope over the declaration body, even if the -XScopedTypeVariables is enabled. See #16635 and #16734. * Wildcards are not allowed in standalone kind signatures, as partial signatures do not allow for polymorphic recursion. * Associated types may not be given an explicit standalone kind signature. Instead, they are assumed to have a CUSK if the parent class has a standalone kind signature and regardless of the -XCUSKs flag. * Standalone kind signatures do not support multiple names at the moment: type T1, T2 :: Type -> Type -- rejected type T1 = Maybe type T2 = Either String See #16754. * Creative use of equality constraints in standalone kind signatures may lead to GHC panics: type C :: forall (a :: Type) -> a ~ Int => Constraint class C a where f :: C a => a -> Int See #16758. Implementation notes -------------------- * The heart of this patch is the 'kcDeclHeader' function, which is used to kind-check a declaration header against its standalone kind signature. It does so in two rounds: 1. check user-written binders 2. instantiate invisible binders a la 'checkExpectedKind' * 'kcTyClGroup' now partitions declarations into declarations with a standalone kind signature or a CUSK (kinded_decls) and declarations without either (kindless_decls): * 'kinded_decls' are kind-checked with 'checkInitialKinds' * 'kindless_decls' are kind-checked with 'getInitialKinds' * DerivInfo has been extended with a new field: di_scoped_tvs :: ![(Name,TyVar)] These variables must be added to the context in case the deriving clause references tcTyConScopedTyVars. See #16731.
Diffstat (limited to 'testsuite/tests/ghci')
-rw-r--r--testsuite/tests/ghci/prog008/ghci.prog008.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/T10018.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/T10059.stdout7
-rw-r--r--testsuite/tests/ghci/scripts/T11051a.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T11051b.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T12005.stdout3
-rw-r--r--testsuite/tests/ghci/scripts/T12550.stdout9
-rw-r--r--testsuite/tests/ghci/scripts/T13407.stdout3
-rw-r--r--testsuite/tests/ghci/scripts/T13420.stdout3
-rw-r--r--testsuite/tests/ghci/scripts/T13699.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/T15341.stdout6
-rw-r--r--testsuite/tests/ghci/scripts/T15546.stdout6
-rw-r--r--testsuite/tests/ghci/scripts/T15827.stdout11
-rw-r--r--testsuite/tests/ghci/scripts/T15872.stdout9
-rw-r--r--testsuite/tests/ghci/scripts/T15941.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T16030.stdout14
-rw-r--r--testsuite/tests/ghci/scripts/T16527.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T4015.stdout17
-rw-r--r--testsuite/tests/ghci/scripts/T4087.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/T4175.stdout31
-rw-r--r--testsuite/tests/ghci/scripts/T5417.stdout6
-rw-r--r--testsuite/tests/ghci/scripts/T5820.stdout8
-rw-r--r--testsuite/tests/ghci/scripts/T6027ghci.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/T7627.stdout19
-rw-r--r--testsuite/tests/ghci/scripts/T7730.stdout6
-rw-r--r--testsuite/tests/ghci/scripts/T7872.stdout8
-rw-r--r--testsuite/tests/ghci/scripts/T7873.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/T7939.stdout22
-rw-r--r--testsuite/tests/ghci/scripts/T8469.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/T8535.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/T8579.stdout8
-rw-r--r--testsuite/tests/ghci/scripts/T8674.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/T9181.stdout82
-rw-r--r--testsuite/tests/ghci/scripts/T9881.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/ghci008.stdout5
-rw-r--r--testsuite/tests/ghci/scripts/ghci011.stdout12
-rw-r--r--testsuite/tests/ghci/scripts/ghci019.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/ghci020.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/ghci023.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/ghci025.stdout18
-rw-r--r--testsuite/tests/ghci/scripts/ghci026.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/ghci027.stdout6
-rw-r--r--testsuite/tests/ghci/scripts/ghci030.stdout8
-rw-r--r--testsuite/tests/ghci/scripts/ghci031.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/ghci033.stdout1
-rw-r--r--testsuite/tests/ghci/scripts/ghci040.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/ghci041.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/ghci042.stdout16
-rw-r--r--testsuite/tests/ghci/scripts/ghci051.stdout24
-rw-r--r--testsuite/tests/ghci/scripts/ghci059.stdout3
-rw-r--r--testsuite/tests/ghci/should_run/T10145.stdout4
-rw-r--r--testsuite/tests/ghci/should_run/T11825.stdout1
-rw-r--r--testsuite/tests/ghci/should_run/T12525.stdout1
-rw-r--r--testsuite/tests/ghci/should_run/T9914.stdout8
54 files changed, 317 insertions, 121 deletions
diff --git a/testsuite/tests/ghci/prog008/ghci.prog008.stdout b/testsuite/tests/ghci/prog008/ghci.prog008.stdout
index 5601247c3c..41efe8294b 100644
--- a/testsuite/tests/ghci/prog008/ghci.prog008.stdout
+++ b/testsuite/tests/ghci/prog008/ghci.prog008.stdout
@@ -1,8 +1,10 @@
+type C :: * -> * -> Constraint
class C a b where
c1 :: Num b => a -> b
c2 :: (Num b, Show b) => a -> b
c3 :: a1 -> b
{-# MINIMAL c1, c2, c3 #-}
+type C :: * -> * -> Constraint
class C a b where
c1 :: Num b => a -> b
c2 :: (Num b, Show b) => a -> b
diff --git a/testsuite/tests/ghci/scripts/T10018.stdout b/testsuite/tests/ghci/scripts/T10018.stdout
index 4f7d4807b2..069ea31d19 100644
--- a/testsuite/tests/ghci/scripts/T10018.stdout
+++ b/testsuite/tests/ghci/scripts/T10018.stdout
@@ -1,2 +1,4 @@
-data Infix a b = a :@: b -- Defined at <interactive>:2:18
+type Infix :: * -> * -> *
+data Infix a b = a :@: b
+ -- Defined at <interactive>:2:18
infixl 4 :@:
diff --git a/testsuite/tests/ghci/scripts/T10059.stdout b/testsuite/tests/ghci/scripts/T10059.stdout
index 955c95a966..3832719cee 100644
--- a/testsuite/tests/ghci/scripts/T10059.stdout
+++ b/testsuite/tests/ghci/scripts/T10059.stdout
@@ -1,4 +1,7 @@
-class (a ~ b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’
+type (~) :: forall k. k -> k -> Constraint
+class (a ~ b) => (~) a b
+ -- Defined in ‘GHC.Types’
(~) :: k -> k -> Constraint
-class (a GHC.Prim.~# b) => (~) (a :: k) (b :: k)
+type (~) :: forall k. k -> k -> Constraint
+class (a GHC.Prim.~# b) => (~) a b
-- Defined in ‘GHC.Types’
diff --git a/testsuite/tests/ghci/scripts/T11051a.stdout b/testsuite/tests/ghci/scripts/T11051a.stdout
index 44fb93cae5..0a380fecd5 100644
--- a/testsuite/tests/ghci/scripts/T11051a.stdout
+++ b/testsuite/tests/ghci/scripts/T11051a.stdout
@@ -1 +1,2 @@
+type Hi :: *
data Hi
diff --git a/testsuite/tests/ghci/scripts/T11051b.stdout b/testsuite/tests/ghci/scripts/T11051b.stdout
index 613bf15c3a..8eea41e3a5 100644
--- a/testsuite/tests/ghci/scripts/T11051b.stdout
+++ b/testsuite/tests/ghci/scripts/T11051b.stdout
@@ -1 +1,2 @@
+type Hello :: *
data Hello = ...
diff --git a/testsuite/tests/ghci/scripts/T12005.stdout b/testsuite/tests/ghci/scripts/T12005.stdout
index 34cde4ad97..5e4b70ca6e 100644
--- a/testsuite/tests/ghci/scripts/T12005.stdout
+++ b/testsuite/tests/ghci/scripts/T12005.stdout
@@ -1,4 +1,5 @@
-class Defer (p :: Constraint) where
+type Defer :: Constraint -> Constraint
+class Defer p where
defer :: (p => r) -> r
{-# MINIMAL defer #-}
-- Defined at <interactive>:5:1
diff --git a/testsuite/tests/ghci/scripts/T12550.stdout b/testsuite/tests/ghci/scripts/T12550.stdout
index c7173fc426..81be552e5c 100644
--- a/testsuite/tests/ghci/scripts/T12550.stdout
+++ b/testsuite/tests/ghci/scripts/T12550.stdout
@@ -11,12 +11,14 @@ f ∷ ∀ {a ∷ ★ → ★} {b}. C a ⇒ a b
f ∷ ∀ {a ∷ ★ → ★} {b}. C a ⇒ a b
f ∷ ∀ {a ∷ ★ → ★} {b}. C a ⇒ a b
fmap ∷ ∀ {f ∷ ★ → ★} {a} {b}. Functor f ⇒ (a → b) → f a → f b
-class Functor (f ∷ ★ → ★) where
+type Functor :: (★ → ★) → Constraint
+class Functor f where
fmap ∷ ∀ a b. (a → b) → f a → f b
...
-- Defined in ‘GHC.Base’
Functor ∷ (★ → ★) → Constraint
-class Functor (f ∷ ★ → ★) where
+type Functor :: (★ → ★) → Constraint
+class Functor f where
fmap ∷ ∀ a b. (a → b) → f a → f b
(<$) ∷ ∀ a b. a → f b → f a
{-# MINIMAL fmap #-}
@@ -56,7 +58,8 @@ datatypeName
∷ ∀ {d} {t ∷ ★ → (★ → ★) → ★ → ★} {f ∷ ★ → ★} {a}.
Datatype d ⇒
t d f a → [Char]
-class Datatype (d ∷ k) where
+type Datatype :: ∀ {k}. k → Constraint
+class Datatype d where
datatypeName ∷ ∀ k1 (t ∷ k → (k1 → ★) → k1 → ★) (f ∷ k1 → ★)
(a ∷ k1).
t d f a → [Char]
diff --git a/testsuite/tests/ghci/scripts/T13407.stdout b/testsuite/tests/ghci/scripts/T13407.stdout
index 083f3a8b1f..85d73d9e89 100644
--- a/testsuite/tests/ghci/scripts/T13407.stdout
+++ b/testsuite/tests/ghci/scripts/T13407.stdout
@@ -1,3 +1,4 @@
type role Foo phantom phantom
-data Foo (a :: * -> *) (b :: k)
+type Foo :: (* -> *) -> forall k. k -> *
+data Foo a b
-- Defined at <interactive>:3:1
diff --git a/testsuite/tests/ghci/scripts/T13420.stdout b/testsuite/tests/ghci/scripts/T13420.stdout
index c6dbaf2755..030b902677 100644
--- a/testsuite/tests/ghci/scripts/T13420.stdout
+++ b/testsuite/tests/ghci/scripts/T13420.stdout
@@ -1,4 +1,5 @@
-type family F a :: * where
+type F :: * -> *
+type family F a where
F [Int] = Bool
F [a] = Double
F (a b) = Char
diff --git a/testsuite/tests/ghci/scripts/T13699.stdout b/testsuite/tests/ghci/scripts/T13699.stdout
index b5950a757b..7c30448563 100644
--- a/testsuite/tests/ghci/scripts/T13699.stdout
+++ b/testsuite/tests/ghci/scripts/T13699.stdout
@@ -1,8 +1,10 @@
+type Foo :: *
data Foo
= Foo {foo1 :: Int,
foo2 :: !Int,
foo3 :: Maybe Int,
foo4 :: !(Maybe Int)}
-- Defined at T13699.hs:3:1
+type Bar :: *
data Bar = Bar Int !Int (Maybe Int) !(Maybe Int)
-- Defined at T13699.hs:10:1
diff --git a/testsuite/tests/ghci/scripts/T15341.stdout b/testsuite/tests/ghci/scripts/T15341.stdout
index e2555f9ac9..403b50456b 100644
--- a/testsuite/tests/ghci/scripts/T15341.stdout
+++ b/testsuite/tests/ghci/scripts/T15341.stdout
@@ -1,6 +1,8 @@
-type family Foo (a :: k) :: k where
+type Foo :: forall k. k -> k
+type family Foo a where
forall k (a :: k). Foo a = a
-- Defined at T15341.hs:5:1
-type family Foo @k (a :: k) :: k where
+type Foo :: forall k. k -> k
+type family Foo @k a where
forall k (a :: k). Foo @k a = a
-- Defined at T15341.hs:5:1
diff --git a/testsuite/tests/ghci/scripts/T15546.stdout b/testsuite/tests/ghci/scripts/T15546.stdout
index 5dc8cf3679..d14b442bb8 100644
--- a/testsuite/tests/ghci/scripts/T15546.stdout
+++ b/testsuite/tests/ghci/scripts/T15546.stdout
@@ -1,8 +1,10 @@
-type family E a b :: * where
+type E :: * -> * -> *
+type family E a b where
E a a = ()
E a b = Bool
-- Defined at <interactive>:2:1
-type family E a b :: * where
+type E :: * -> * -> *
+type family E a b where
{- #0 -} E a a = ()
{- #1 -} E a b = Bool
-- incompatible with: #0
diff --git a/testsuite/tests/ghci/scripts/T15827.stdout b/testsuite/tests/ghci/scripts/T15827.stdout
index 50df504e58..8b403d4043 100644
--- a/testsuite/tests/ghci/scripts/T15827.stdout
+++ b/testsuite/tests/ghci/scripts/T15827.stdout
@@ -1,9 +1,14 @@
-type family F1 (a :: k) :: * -- Defined at T15827.hs:9:1
+type F1 :: forall k. k -> *
+type family F1 a
+ -- Defined at T15827.hs:9:1
type instance forall k (a :: k). F1 a = Proxy a
-- Defined at T15827.hs:10:34
-type family F2 (a :: k) :: * where
+type F2 :: forall k. k -> *
+type family F2 a where
forall k (a :: k). F2 a = Proxy a
-- Defined at T15827.hs:12:1
-data family D (a :: k) -- Defined at T15827.hs:15:1
+type D :: forall k. k -> *
+data family D a
+ -- Defined at T15827.hs:15:1
data instance forall k (a :: k). D a = MkD (Proxy a)
-- Defined at T15827.hs:16:34
diff --git a/testsuite/tests/ghci/scripts/T15872.stdout b/testsuite/tests/ghci/scripts/T15872.stdout
index 623631162a..e1aa200425 100644
--- a/testsuite/tests/ghci/scripts/T15872.stdout
+++ b/testsuite/tests/ghci/scripts/T15872.stdout
@@ -1,5 +1,6 @@
MkFun :: (a -> b) -> Fun a b
Fun :: (a ~ 'OP) => * -> * -> *
+type Fun :: forall (a :: WHICH). (a ~ 'OP) => * -> * -> *
data Fun b c where
MkFun :: (b -> c) -> Fun b c
-- Defined at T15872.hs:11:1
@@ -7,10 +8,10 @@ MkFun
:: (a -> b) -> Fun @'OP @{'GHC.Types.Eq# @WHICH @'OP @'OP <>} a b
Fun :: ((a :: WHICH) ~ ('OP :: WHICH)) => * -> * -> *
type role Fun nominal nominal representational representational
-data Fun @(a :: WHICH)
- @{a1 :: (a :: WHICH) ~ ('OP :: WHICH)}
- b
- c where
+type Fun :: forall (a :: WHICH).
+ ((a :: WHICH) ~ ('OP :: WHICH)) =>
+ * -> * -> *
+data Fun @a @{a1} b c where
MkFun :: (b -> c)
-> Fun @'OP @{'GHC.Types.Eq# @WHICH @'OP @'OP <>} b c
-- Defined at T15872.hs:11:1
diff --git a/testsuite/tests/ghci/scripts/T15941.stdout b/testsuite/tests/ghci/scripts/T15941.stdout
index c6f31a7334..f9e6d339f9 100644
--- a/testsuite/tests/ghci/scripts/T15941.stdout
+++ b/testsuite/tests/ghci/scripts/T15941.stdout
@@ -1,3 +1,4 @@
+type T :: * -> * -> *
type T =
(->) @{'GHC.Types.LiftedRep} @{'GHC.Types.LiftedRep} :: * -> * -> *
-- Defined at <interactive>:2:1
diff --git a/testsuite/tests/ghci/scripts/T16030.stdout b/testsuite/tests/ghci/scripts/T16030.stdout
index d1691a6758..4efa27ce70 100644
--- a/testsuite/tests/ghci/scripts/T16030.stdout
+++ b/testsuite/tests/ghci/scripts/T16030.stdout
@@ -1,20 +1,26 @@
type role Foo1 phantom
-data Foo1 (a :: k) where
+type Foo1 :: forall k. k -> *
+data Foo1 a where
MkFoo1a :: forall k (a :: k). Proxy a -> Int -> Foo1 a
MkFoo1b :: forall k (a :: k). {a :: Proxy a, b :: Int} -> Foo1 a
-- Defined at T16030.hs:8:1
-data family Foo2 (a :: k) -- Defined at T16030.hs:12:1
+type Foo2 :: forall k. k -> *
+data family Foo2 a
+ -- Defined at T16030.hs:12:1
data instance forall k (a :: k). Foo2 a where
MkFoo2a :: forall k (a :: k). Proxy a -> Int -> Foo2 a
MkFoo2b :: forall k (a :: k). {c :: Proxy a, d :: Int} -> Foo2 a
-- Defined at T16030.hs:13:15
type role Foo1 nominal phantom
-data Foo1 @k (a :: k) where
+type Foo1 :: forall k. k -> *
+data Foo1 @k a where
MkFoo1a :: forall k (a :: k). Proxy @{k} a -> Int -> Foo1 @k a
MkFoo1b :: forall k (a :: k).
{a :: Proxy @{k} a, b :: Int} -> Foo1 @k a
-- Defined at T16030.hs:8:1
-data family Foo2 @k (a :: k) -- Defined at T16030.hs:12:1
+type Foo2 :: forall k. k -> *
+data family Foo2 @k a
+ -- Defined at T16030.hs:12:1
data instance forall k (a :: k). Foo2 @k a where
MkFoo2a :: forall k (a :: k). Proxy @{k} a -> Int -> Foo2 @k a
MkFoo2b :: forall k (a :: k).
diff --git a/testsuite/tests/ghci/scripts/T16527.stdout b/testsuite/tests/ghci/scripts/T16527.stdout
index fd4e0ef735..40688b571e 100644
--- a/testsuite/tests/ghci/scripts/T16527.stdout
+++ b/testsuite/tests/ghci/scripts/T16527.stdout
@@ -1,3 +1,4 @@
+type T :: *
data T where
MkT1 :: (Int -> Int) -> T
MkT2 :: (forall a. Maybe a) -> T
diff --git a/testsuite/tests/ghci/scripts/T4015.stdout b/testsuite/tests/ghci/scripts/T4015.stdout
index 4ce312c581..cd8867212b 100644
--- a/testsuite/tests/ghci/scripts/T4015.stdout
+++ b/testsuite/tests/ghci/scripts/T4015.stdout
@@ -1,20 +1,31 @@
+type R :: *
data R
= R {x :: Char, y :: Int, z :: Float}
| S {x :: Char}
| T {y :: Int, z :: Float}
| W
+type R :: *
data R
= R {x :: Char, y :: Int, z :: Float}
| S {x :: Char}
| T {y :: Int, z :: Float}
| W
-- Defined at T4015.hs:3:1
-data R = ... | S {...} | ... -- Defined at T4015.hs:4:10
-data R = ... | T {...} | ... -- Defined at T4015.hs:5:10
-data R = ... | W -- Defined at T4015.hs:6:10
+type R :: *
+data R = ... | S {...} | ...
+ -- Defined at T4015.hs:4:10
+type R :: *
+data R = ... | T {...} | ...
+ -- Defined at T4015.hs:5:10
+type R :: *
+data R = ... | W
+ -- Defined at T4015.hs:6:10
+type R :: *
data R = R {x :: Char, ...} | S {x :: Char} | ...
-- Defined at T4015.hs:3:14
+type R :: *
data R = R {..., y :: Int, ...} | ... | T {y :: Int, ...} | ...
-- Defined at T4015.hs:3:25
+type R :: *
data R = R {..., z :: Float} | ... | T {..., z :: Float} | ...
-- Defined at T4015.hs:3:35
diff --git a/testsuite/tests/ghci/scripts/T4087.stdout b/testsuite/tests/ghci/scripts/T4087.stdout
index 3f600bd78d..8dafaa881d 100644
--- a/testsuite/tests/ghci/scripts/T4087.stdout
+++ b/testsuite/tests/ghci/scripts/T4087.stdout
@@ -1,4 +1,5 @@
type role Equal nominal nominal
+type Equal :: * -> * -> *
data Equal a b where
Equal :: Equal a a
-- Defined at T4087.hs:5:1
diff --git a/testsuite/tests/ghci/scripts/T4175.stdout b/testsuite/tests/ghci/scripts/T4175.stdout
index 9dfcd6c0d6..52d8a688c7 100644
--- a/testsuite/tests/ghci/scripts/T4175.stdout
+++ b/testsuite/tests/ghci/scripts/T4175.stdout
@@ -1,21 +1,30 @@
-type family A a b :: * -- Defined at T4175.hs:7:1
+type A :: * -> * -> *
+type family A a b
+ -- Defined at T4175.hs:7:1
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
+type B :: * -> *
+data family B a
+ -- Defined at T4175.hs:12:1
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
+type C :: * -> Constraint
class C a where
- type family D a b :: *
+ type D :: * -> * -> *
+ type family D a b
-- Defined at T4175.hs:16:5
type instance D () () = Bool -- Defined at T4175.hs:22:10
type instance D Int () = String -- Defined at T4175.hs:19:10
-type family E a :: * where
+type E :: * -> *
+type family E a where
E () = Bool
E Int = String
-- Defined at T4175.hs:24:1
-data () = () -- Defined in ‘GHC.Tuple’
+type () :: *
+data () = ()
+ -- Defined in ‘GHC.Tuple’
instance [safe] C () -- Defined at T4175.hs:21:10
instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’
@@ -28,7 +37,9 @@ instance Bounded () -- Defined in ‘GHC.Enum’
type instance D () () = Bool -- Defined at T4175.hs:22:10
type instance D Int () = String -- Defined at T4175.hs:19:10
data instance B () = MkB -- Defined at T4175.hs:13:15
-data Maybe a = Nothing | Just a -- Defined in ‘GHC.Maybe’
+type Maybe :: * -> *
+data Maybe a = Nothing | Just a
+ -- Defined in ‘GHC.Maybe’
instance Applicative Maybe -- Defined in ‘GHC.Base’
instance Eq a => Eq (Maybe a) -- Defined in ‘GHC.Maybe’
instance Functor Maybe -- Defined in ‘GHC.Base’
@@ -43,7 +54,9 @@ 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 = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’
+type Int :: *
+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’
@@ -56,5 +69,7 @@ instance Bounded Int -- Defined in ‘GHC.Enum’
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
+type Z :: * -> Constraint
+class Z a
+ -- Defined at T4175.hs:28:1
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 ab2827730f..163a9236de 100644
--- a/testsuite/tests/ghci/scripts/T5417.stdout
+++ b/testsuite/tests/ghci/scripts/T5417.stdout
@@ -1,9 +1,15 @@
+type B1 :: * -> *
data B1 a = B1 a
data instance C.F (B1 a) = B2 a
+type D :: * -> *
data family D a
+type C.C1 :: * -> Constraint
class C.C1 a where
+ type C.F :: * -> *
data family C.F a
+type C.C1 :: * -> Constraint
class C.C1 a where
+ type C.F :: * -> *
data family C.F a
-- 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/T5820.stdout b/testsuite/tests/ghci/scripts/T5820.stdout
index a8dddd3863..faa5f6fc76 100644
--- a/testsuite/tests/ghci/scripts/T5820.stdout
+++ b/testsuite/tests/ghci/scripts/T5820.stdout
@@ -1,4 +1,8 @@
-data Foo = Foo -- Defined at T5820.hs:2:1
+type Foo :: *
+data Foo = Foo
+ -- Defined at T5820.hs:2:1
instance [safe] Eq Foo -- Defined at T5820.hs:3:10
-data Foo = Foo -- Defined at T5820.hs:2:1
+type Foo :: *
+data Foo = Foo
+ -- Defined at T5820.hs:2:1
instance [safe] Eq Foo -- Defined at T5820.hs:3:10
diff --git a/testsuite/tests/ghci/scripts/T6027ghci.stdout b/testsuite/tests/ghci/scripts/T6027ghci.stdout
index be1034b0c7..7711a3003f 100644
--- a/testsuite/tests/ghci/scripts/T6027ghci.stdout
+++ b/testsuite/tests/ghci/scripts/T6027ghci.stdout
@@ -1 +1,3 @@
-data (?) -- Defined at <interactive>:2:1
+type (?) :: *
+data (?)
+ -- Defined at <interactive>:2:1
diff --git a/testsuite/tests/ghci/scripts/T7627.stdout b/testsuite/tests/ghci/scripts/T7627.stdout
index ea9aaafb80..b86ea432ff 100644
--- a/testsuite/tests/ghci/scripts/T7627.stdout
+++ b/testsuite/tests/ghci/scripts/T7627.stdout
@@ -1,4 +1,6 @@
-data () = () -- Defined in ‘GHC.Tuple’
+type () :: *
+data () = ()
+ -- Defined in ‘GHC.Tuple’
instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’
instance Ord () -- Defined in ‘GHC.Classes’
@@ -7,12 +9,16 @@ instance Enum () -- Defined in ‘GHC.Enum’
instance Show () -- Defined in ‘GHC.Show’
instance Read () -- Defined in ‘GHC.Read’
instance Bounded () -- Defined in ‘GHC.Enum’
-data (##) = (##) -- Defined in ‘GHC.Prim’
+type (##) :: TYPE ('GHC.Types.TupleRep '[])
+data (##) = (##)
+ -- Defined in ‘GHC.Prim’
() :: ()
(##) :: (# #)
( ) :: ()
(# #) :: (# #)
-data (,) a b = (,) a b -- Defined in ‘GHC.Tuple’
+type (,) :: * -> * -> *
+data (,) a b = (,) a b
+ -- Defined in ‘GHC.Tuple’
instance Monoid a => Applicative ((,) a) -- Defined in ‘GHC.Base’
instance (Eq a, Eq b) => Eq (a, b) -- Defined in ‘GHC.Classes’
instance Functor ((,) a) -- Defined in ‘GHC.Base’
@@ -28,7 +34,12 @@ instance Foldable ((,) a) -- Defined in ‘Data.Foldable’
instance Traversable ((,) a) -- Defined in ‘Data.Traversable’
instance (Bounded a, Bounded b) => Bounded (a, b)
-- Defined in ‘GHC.Enum’
-data (#,#) (a :: TYPE k0) (b :: TYPE k1) = (#,#) a b
+type (#,#) :: *
+ -> *
+ -> TYPE
+ ('GHC.Types.TupleRep
+ '[ 'GHC.Types.LiftedRep, 'GHC.Types.LiftedRep])
+data (#,#) a b = (#,#) a b
-- Defined in ‘GHC.Prim’
(,) :: a -> b -> (a, b)
(#,#) :: a -> b -> (# a, b #)
diff --git a/testsuite/tests/ghci/scripts/T7730.stdout b/testsuite/tests/ghci/scripts/T7730.stdout
index bf9c1d025b..9c3e385c71 100644
--- a/testsuite/tests/ghci/scripts/T7730.stdout
+++ b/testsuite/tests/ghci/scripts/T7730.stdout
@@ -1,7 +1,9 @@
type role A phantom phantom
-data A (x :: k) (y :: k1)
+type A :: forall k k1. k -> k1 -> *
+data A x y
-- Defined at <interactive>:2:1
A :: k1 -> k2 -> *
type role T phantom
-data T (a :: k) = forall a1. MkT a1
+type T :: forall k. k -> *
+data T a = forall a1. MkT a1
-- Defined at <interactive>:6:1
diff --git a/testsuite/tests/ghci/scripts/T7872.stdout b/testsuite/tests/ghci/scripts/T7872.stdout
index 4c577ce1cd..4c8c1dd772 100644
--- a/testsuite/tests/ghci/scripts/T7872.stdout
+++ b/testsuite/tests/ghci/scripts/T7872.stdout
@@ -1,2 +1,6 @@
-type T = forall a. a -> a -- Defined at <interactive>:2:1
-data D = MkT (forall b. b -> b) -- Defined at <interactive>:3:1
+type T :: *
+type T = forall a. a -> a
+ -- Defined at <interactive>:2:1
+type D :: *
+data D = MkT (forall b. b -> b)
+ -- Defined at <interactive>:3:1
diff --git a/testsuite/tests/ghci/scripts/T7873.stdout b/testsuite/tests/ghci/scripts/T7873.stdout
index bcdebe71e1..4abcab8c18 100644
--- a/testsuite/tests/ghci/scripts/T7873.stdout
+++ b/testsuite/tests/ghci/scripts/T7873.stdout
@@ -1,5 +1,7 @@
+type D2 :: *
data D2
= forall k. MkD2 (forall (p :: k -> *) (a :: k). p a -> Int)
-- Defined at <interactive>:3:1
+type D3 :: *
data D3 = MkD3 (forall k (p :: k -> *) (a :: k). p a -> Int)
-- Defined at <interactive>:4:1
diff --git a/testsuite/tests/ghci/scripts/T7939.stdout b/testsuite/tests/ghci/scripts/T7939.stdout
index 4c2a602f4f..1b6b04e3f9 100644
--- a/testsuite/tests/ghci/scripts/T7939.stdout
+++ b/testsuite/tests/ghci/scripts/T7939.stdout
@@ -1,24 +1,32 @@
-class Foo (a :: k) where
- type family Bar (a :: k) b :: *
+type Foo :: forall k. k -> Constraint
+class Foo a where
+ type Bar :: forall k. k -> * -> *
+ type family Bar a b
-- Defined at T7939.hs:6:4
Bar :: k -> * -> *
-type family F a :: * -- Defined at T7939.hs:8:1
+type F :: * -> *
+type family F a
+ -- Defined at T7939.hs:8:1
type instance F Int = Bool -- Defined at T7939.hs:9:15
F :: * -> *
-type family G a :: * where
+type G :: * -> *
+type family G a where
G Int = Bool
-- Defined at T7939.hs:11:1
G :: * -> *
-type family H (a :: Bool) :: Bool where
+type H :: Bool -> Bool
+type family H a where
H 'False = 'True
-- Defined at T7939.hs:14:1
H :: Bool -> Bool
-type family J (a :: [k]) :: Bool where
+type J :: forall k. [k] -> Bool
+type family J a where
J '[] = 'False
forall k (h :: k) (t :: [k]). J (h : t) = 'True
-- Defined at T7939.hs:17:1
J :: [k] -> Bool
-type family K (a1 :: [a]) :: Maybe a where
+type K :: forall a. [a] -> Maybe a
+type family K a1 where
K '[] = 'Nothing
forall a (h :: a) (t :: [a]). K (h : t) = 'Just h
-- Defined at T7939.hs:21:1
diff --git a/testsuite/tests/ghci/scripts/T8469.stdout b/testsuite/tests/ghci/scripts/T8469.stdout
index 1a511e6b55..7cad316fee 100644
--- a/testsuite/tests/ghci/scripts/T8469.stdout
+++ b/testsuite/tests/ghci/scripts/T8469.stdout
@@ -1,4 +1,6 @@
-data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’
+type Int :: *
+data Int = GHC.Types.I# GHC.Prim.Int#
+ -- Defined in ‘GHC.Types’
instance Eq Int -- Defined in ‘GHC.Classes’
instance Ord Int -- Defined in ‘GHC.Classes’
instance Enum Int -- Defined in ‘GHC.Enum’
diff --git a/testsuite/tests/ghci/scripts/T8535.stdout b/testsuite/tests/ghci/scripts/T8535.stdout
index 4effb90a52..7a949cd465 100644
--- a/testsuite/tests/ghci/scripts/T8535.stdout
+++ b/testsuite/tests/ghci/scripts/T8535.stdout
@@ -1,4 +1,6 @@
-data (->) (a :: TYPE q) (b :: TYPE r) -- Defined in ‘GHC.Prim’
+type (->) :: * -> * -> *
+data (->) a b
+ -- Defined in ‘GHC.Prim’
infixr -1 ->
instance Applicative ((->) r) -- Defined in ‘GHC.Base’
instance Functor ((->) r) -- Defined in ‘GHC.Base’
diff --git a/testsuite/tests/ghci/scripts/T8579.stdout b/testsuite/tests/ghci/scripts/T8579.stdout
index 2db09d7fd4..b9f7c748f4 100644
--- a/testsuite/tests/ghci/scripts/T8579.stdout
+++ b/testsuite/tests/ghci/scripts/T8579.stdout
@@ -1,2 +1,6 @@
-data A = Y -- Defined at <interactive>:2:1
-data A = Y -- Defined at <interactive>:2:1
+type A :: *
+data A = Y
+ -- Defined at <interactive>:2:1
+type A :: *
+data A = Y
+ -- Defined at <interactive>:2:1
diff --git a/testsuite/tests/ghci/scripts/T8674.stdout b/testsuite/tests/ghci/scripts/T8674.stdout
index d938f95692..7d7beeb1cd 100644
--- a/testsuite/tests/ghci/scripts/T8674.stdout
+++ b/testsuite/tests/ghci/scripts/T8674.stdout
@@ -1,4 +1,6 @@
-data family Sing (a :: k) -- Defined at T8674.hs:4:1
+type Sing :: forall k. k -> *
+data family Sing a
+ -- Defined at T8674.hs:4:1
data instance Sing Bool = SBool -- Defined at T8674.hs:6:15
data instance forall k (a :: [k]). Sing a = SNil
-- Defined at T8674.hs:5:15
diff --git a/testsuite/tests/ghci/scripts/T9181.stdout b/testsuite/tests/ghci/scripts/T9181.stdout
index a30879c316..388681ed63 100644
--- a/testsuite/tests/ghci/scripts/T9181.stdout
+++ b/testsuite/tests/ghci/scripts/T9181.stdout
@@ -1,9 +1,10 @@
-type family GHC.TypeLits.AppendSymbol (a :: GHC.Types.Symbol)
- (b :: GHC.Types.Symbol)
- :: GHC.Types.Symbol
-type family GHC.TypeLits.CmpSymbol (a :: GHC.Types.Symbol)
- (b :: GHC.Types.Symbol)
- :: Ordering
+type GHC.TypeLits.AppendSymbol :: GHC.Types.Symbol
+ -> GHC.Types.Symbol -> GHC.Types.Symbol
+type family GHC.TypeLits.AppendSymbol a b
+type GHC.TypeLits.CmpSymbol :: GHC.Types.Symbol
+ -> GHC.Types.Symbol -> Ordering
+type family GHC.TypeLits.CmpSymbol a b
+type GHC.TypeLits.ErrorMessage :: *
data GHC.TypeLits.ErrorMessage
= GHC.TypeLits.Text GHC.Types.Symbol
| forall t. GHC.TypeLits.ShowType t
@@ -13,15 +14,18 @@ data GHC.TypeLits.ErrorMessage
| GHC.TypeLits.ErrorMessage
GHC.TypeLits.:$$:
GHC.TypeLits.ErrorMessage
-class GHC.TypeLits.KnownSymbol (n :: GHC.Types.Symbol) where
+type GHC.TypeLits.KnownSymbol :: GHC.Types.Symbol -> Constraint
+class GHC.TypeLits.KnownSymbol n where
GHC.TypeLits.symbolSing :: GHC.TypeLits.SSymbol n
{-# MINIMAL symbolSing #-}
+type GHC.TypeLits.SomeSymbol :: *
data GHC.TypeLits.SomeSymbol
= forall (n :: GHC.Types.Symbol).
GHC.TypeLits.KnownSymbol n =>
GHC.TypeLits.SomeSymbol (Data.Proxy.Proxy n)
-type family GHC.TypeLits.TypeError (a :: GHC.TypeLits.ErrorMessage)
- :: b where
+type GHC.TypeLits.TypeError :: forall b.
+ GHC.TypeLits.ErrorMessage -> b
+type family GHC.TypeLits.TypeError a where
GHC.TypeLits.natVal ::
GHC.TypeNats.KnownNat n => proxy n -> Integer
GHC.TypeLits.natVal' ::
@@ -36,42 +40,48 @@ GHC.TypeLits.symbolVal ::
GHC.TypeLits.KnownSymbol n => proxy n -> String
GHC.TypeLits.symbolVal' ::
GHC.TypeLits.KnownSymbol n => GHC.Prim.Proxy# n -> String
-type family (GHC.TypeNats.*) (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: GHC.Types.Nat
-type family (GHC.TypeNats.+) (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: GHC.Types.Nat
-type family (GHC.TypeNats.-) (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: GHC.Types.Nat
-type (GHC.TypeNats.<=) (x :: GHC.Types.Nat) (y :: GHC.Types.Nat) =
+type (GHC.TypeNats.*) :: GHC.Types.Nat
+ -> GHC.Types.Nat -> GHC.Types.Nat
+type family (GHC.TypeNats.*) a b
+type (GHC.TypeNats.+) :: GHC.Types.Nat
+ -> GHC.Types.Nat -> GHC.Types.Nat
+type family (GHC.TypeNats.+) a b
+type (GHC.TypeNats.-) :: GHC.Types.Nat
+ -> GHC.Types.Nat -> GHC.Types.Nat
+type family (GHC.TypeNats.-) a b
+type (GHC.TypeNats.<=) :: GHC.Types.Nat
+ -> GHC.Types.Nat -> Constraint
+type (GHC.TypeNats.<=) x y =
(x GHC.TypeNats.<=? y) ~ 'True :: Constraint
-type family (GHC.TypeNats.<=?) (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: Bool
-type family GHC.TypeNats.CmpNat (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: Ordering
-type family GHC.TypeNats.Div (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: GHC.Types.Nat
-class GHC.TypeNats.KnownNat (n :: GHC.Types.Nat) where
+type (GHC.TypeNats.<=?) :: GHC.Types.Nat -> GHC.Types.Nat -> Bool
+type family (GHC.TypeNats.<=?) a b
+type GHC.TypeNats.CmpNat :: GHC.Types.Nat
+ -> GHC.Types.Nat -> Ordering
+type family GHC.TypeNats.CmpNat a b
+type GHC.TypeNats.Div :: GHC.Types.Nat
+ -> GHC.Types.Nat -> GHC.Types.Nat
+type family GHC.TypeNats.Div a b
+type GHC.TypeNats.KnownNat :: GHC.Types.Nat -> Constraint
+class GHC.TypeNats.KnownNat n where
GHC.TypeNats.natSing :: GHC.TypeNats.SNat n
{-# MINIMAL natSing #-}
-type family GHC.TypeNats.Log2 (a :: GHC.Types.Nat) :: GHC.Types.Nat
-type family GHC.TypeNats.Mod (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: GHC.Types.Nat
+type GHC.TypeNats.Log2 :: GHC.Types.Nat -> GHC.Types.Nat
+type family GHC.TypeNats.Log2 a
+type GHC.TypeNats.Mod :: GHC.Types.Nat
+ -> GHC.Types.Nat -> GHC.Types.Nat
+type family GHC.TypeNats.Mod a b
+type GHC.Types.Nat :: *
data GHC.Types.Nat
+type GHC.TypeNats.SomeNat :: *
data GHC.TypeNats.SomeNat
= forall (n :: GHC.Types.Nat).
GHC.TypeNats.KnownNat n =>
GHC.TypeNats.SomeNat (Data.Proxy.Proxy n)
+type GHC.Types.Symbol :: *
data GHC.Types.Symbol
-type family (GHC.TypeNats.^) (a :: GHC.Types.Nat)
- (b :: GHC.Types.Nat)
- :: GHC.Types.Nat
+type (GHC.TypeNats.^) :: GHC.Types.Nat
+ -> GHC.Types.Nat -> GHC.Types.Nat
+type family (GHC.TypeNats.^) a b
GHC.TypeNats.sameNat ::
(GHC.TypeNats.KnownNat a, GHC.TypeNats.KnownNat b) =>
Data.Proxy.Proxy a
diff --git a/testsuite/tests/ghci/scripts/T9881.stdout b/testsuite/tests/ghci/scripts/T9881.stdout
index 68acea7c61..57bc6256d3 100644
--- a/testsuite/tests/ghci/scripts/T9881.stdout
+++ b/testsuite/tests/ghci/scripts/T9881.stdout
@@ -1,3 +1,4 @@
+type Data.ByteString.Lazy.ByteString :: *
data Data.ByteString.Lazy.ByteString
= Data.ByteString.Lazy.Internal.Empty
| Data.ByteString.Lazy.Internal.Chunk {-# UNPACK #-}Data.ByteString.ByteString
@@ -16,6 +17,7 @@ instance Show Data.ByteString.Lazy.ByteString
instance Read Data.ByteString.Lazy.ByteString
-- Defined in ‘Data.ByteString.Lazy.Internal’
+type Data.ByteString.ByteString :: *
data Data.ByteString.ByteString
= Data.ByteString.Internal.PS {-# UNPACK #-}(GHC.ForeignPtr.ForeignPtr
GHC.Word.Word8)
diff --git a/testsuite/tests/ghci/scripts/ghci008.stdout b/testsuite/tests/ghci/scripts/ghci008.stdout
index abed6d21f3..3f62f3f7f2 100644
--- a/testsuite/tests/ghci/scripts/ghci008.stdout
+++ b/testsuite/tests/ghci/scripts/ghci008.stdout
@@ -1,19 +1,24 @@
+type Num :: * -> Constraint
class Num a where
(+) :: a -> a -> a
...
-- Defined in ‘GHC.Num’
infixl 6 +
+type Num :: * -> Constraint
class Num a where
(+) :: a -> a -> a
...
-- Defined in ‘GHC.Num’
infixl 6 +
+type Data.Complex.Complex :: * -> *
data Data.Complex.Complex a = !a Data.Complex.:+ !a
-- Defined in ‘Data.Complex’
infix 6 Data.Complex.:+
+type Data.Complex.Complex :: * -> *
data Data.Complex.Complex a = !a Data.Complex.:+ !a
-- Defined in ‘Data.Complex’
infix 6 Data.Complex.:+
+type RealFloat :: * -> Constraint
class (RealFrac a, Floating a) => RealFloat a where
floatRadix :: a -> Integer
floatDigits :: a -> Int
diff --git a/testsuite/tests/ghci/scripts/ghci011.stdout b/testsuite/tests/ghci/scripts/ghci011.stdout
index 6dd5782d6c..35f4b9fda2 100644
--- a/testsuite/tests/ghci/scripts/ghci011.stdout
+++ b/testsuite/tests/ghci/scripts/ghci011.stdout
@@ -1,4 +1,6 @@
-data [] a = [] | a : [a] -- Defined in ‘GHC.Types’
+type [] :: * -> *
+data [] a = [] | a : [a]
+ -- Defined in ‘GHC.Types’
instance Applicative [] -- Defined in ‘GHC.Base’
instance Eq a => Eq [a] -- Defined in ‘GHC.Classes’
instance Functor [] -- Defined in ‘GHC.Base’
@@ -11,7 +13,9 @@ instance MonadFail [] -- Defined in ‘Control.Monad.Fail’
instance Read a => Read [a] -- Defined in ‘GHC.Read’
instance Foldable [] -- Defined in ‘Data.Foldable’
instance Traversable [] -- Defined in ‘Data.Traversable’
-data () = () -- Defined in ‘GHC.Tuple’
+type () :: *
+data () = ()
+ -- Defined in ‘GHC.Tuple’
instance Eq () -- Defined in ‘GHC.Classes’
instance Monoid () -- Defined in ‘GHC.Base’
instance Ord () -- Defined in ‘GHC.Classes’
@@ -20,7 +24,9 @@ instance Enum () -- Defined in ‘GHC.Enum’
instance Show () -- Defined in ‘GHC.Show’
instance Read () -- Defined in ‘GHC.Read’
instance Bounded () -- Defined in ‘GHC.Enum’
-data (,) a b = (,) a b -- Defined in ‘GHC.Tuple’
+type (,) :: * -> * -> *
+data (,) a b = (,) a b
+ -- Defined in ‘GHC.Tuple’
instance Monoid a => Applicative ((,) a) -- Defined in ‘GHC.Base’
instance (Eq a, Eq b) => Eq (a, b) -- Defined in ‘GHC.Classes’
instance Functor ((,) a) -- Defined in ‘GHC.Base’
diff --git a/testsuite/tests/ghci/scripts/ghci019.stdout b/testsuite/tests/ghci/scripts/ghci019.stdout
index d03720d2b5..0a9fefb77b 100644
--- a/testsuite/tests/ghci/scripts/ghci019.stdout
+++ b/testsuite/tests/ghci/scripts/ghci019.stdout
@@ -1,2 +1,4 @@
-data Foo = Foo -- Defined at ghci019.hs:8:1
+type Foo :: *
+data Foo = Foo
+ -- Defined at ghci019.hs:8:1
instance [safe] Prelude.Eq Foo -- Defined at ghci019.hs:9:10
diff --git a/testsuite/tests/ghci/scripts/ghci020.stdout b/testsuite/tests/ghci/scripts/ghci020.stdout
index 4effb90a52..7a949cd465 100644
--- a/testsuite/tests/ghci/scripts/ghci020.stdout
+++ b/testsuite/tests/ghci/scripts/ghci020.stdout
@@ -1,4 +1,6 @@
-data (->) (a :: TYPE q) (b :: TYPE r) -- Defined in ‘GHC.Prim’
+type (->) :: * -> * -> *
+data (->) a b
+ -- Defined in ‘GHC.Prim’
infixr -1 ->
instance Applicative ((->) r) -- Defined in ‘GHC.Base’
instance Functor ((->) r) -- Defined in ‘GHC.Base’
diff --git a/testsuite/tests/ghci/scripts/ghci023.stdout b/testsuite/tests/ghci/scripts/ghci023.stdout
index 9403102dd9..70c64c4293 100644
--- a/testsuite/tests/ghci/scripts/ghci023.stdout
+++ b/testsuite/tests/ghci/scripts/ghci023.stdout
@@ -12,6 +12,7 @@ Data.Maybe.listToMaybe :: [a] -> Maybe a
Data.Maybe.mapMaybe :: (a -> Maybe b) -> [a] -> [b]
maybe :: b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybeToList :: Maybe a -> [a]
+type Maybe :: * -> *
data Maybe a = Nothing | Just a
-- via readFile
(True,False)
diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout
index 9c862d340c..3531825a97 100644
--- a/testsuite/tests/ghci/scripts/ghci025.stdout
+++ b/testsuite/tests/ghci/scripts/ghci025.stdout
@@ -2,8 +2,11 @@
:browse! *T
-- defined locally
T.length :: T.Integer
+type N :: * -> Constraint
class N a
+type S :: * -> Constraint
class S a
+type C :: * -> * -> Constraint
class C a b
...
c1 :: (C a b, N b) => a -> b
@@ -11,7 +14,8 @@ c2 :: (C a b, N b, S b) => a -> b
c3 :: C a b => a -> b
c4 :: C a b => a1 -> b
-- imported via Control.Monad
-class (GHC.Base.Alternative m, Monad m) => MonadPlus (m :: * -> *)
+type MonadPlus :: (* -> *) -> Constraint
+class (GHC.Base.Alternative m, Monad m) => MonadPlus m
...
mplus :: MonadPlus m => m a -> m a -> m a
mzero :: MonadPlus m => m a
@@ -20,7 +24,8 @@ mzero :: MonadPlus m => m a
(>>=) :: Monad m => m a -> (a -> m b) -> m b
return :: Monad m => a -> m a
-- imported via Control.Monad, Prelude, T
-class GHC.Base.Applicative m => Monad (m :: * -> *)
+type Monad :: (* -> *) -> Constraint
+class GHC.Base.Applicative m => Monad m
...
-- imported via Data.Maybe
catMaybes :: [Maybe a] -> [a]
@@ -34,23 +39,29 @@ maybe :: b -> (a -> b) -> Maybe a -> b
maybeToList :: Maybe a -> [a]
-- imported via Data.Maybe, Prelude
Just :: a -> Maybe a
+type Maybe :: * -> *
data Maybe a = ...
Nothing :: Maybe a
-- imported via Prelude
(+) :: GHC.Num.Num a => a -> a -> a
(=<<) :: Monad m => (a -> m b) -> m a -> m b
+type Eq :: * -> Constraint
class Eq a
...
-- imported via Prelude, T
Prelude.length :: Data.Foldable.Foldable t => t a -> GHC.Types.Int
-- imported via T
+type T.Integer :: *
data T.Integer = ...
T.length :: Data.ByteString.Internal.ByteString -> GHC.Types.Int
:browse! T
-- defined locally
T.length :: T.Integer
+type N :: * -> Constraint
class N a
+type S :: * -> Constraint
class S a
+type C :: * -> * -> Constraint
class C a b
...
c1 :: (C a b, N b) => a -> b
@@ -60,8 +71,11 @@ c4 :: C a b => a1 -> b
:browse! T -- with -fprint-explicit-foralls
-- defined locally
T.length :: T.Integer
+type N :: * -> Constraint
class N a
+type S :: * -> Constraint
class S a
+type C :: * -> * -> Constraint
class C a b
...
c1 :: forall a b. (C a b, N b) => a -> b
diff --git a/testsuite/tests/ghci/scripts/ghci026.stdout b/testsuite/tests/ghci/scripts/ghci026.stdout
index 24049ee655..d8e282a3b2 100644
--- a/testsuite/tests/ghci/scripts/ghci026.stdout
+++ b/testsuite/tests/ghci/scripts/ghci026.stdout
@@ -7,7 +7,9 @@ listToMaybe :: [a] -> Maybe a
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
maybe :: b -> (a -> b) -> Maybe a -> b
maybeToList :: Maybe a -> [a]
+type Maybe :: * -> *
data Maybe a = Nothing | Just a
+type T :: *
data T = A Int | B Float
f :: Double -> Double
g :: Double -> Double
diff --git a/testsuite/tests/ghci/scripts/ghci027.stdout b/testsuite/tests/ghci/scripts/ghci027.stdout
index bbe355c17a..e152e7419a 100644
--- a/testsuite/tests/ghci/scripts/ghci027.stdout
+++ b/testsuite/tests/ghci/scripts/ghci027.stdout
@@ -1,8 +1,10 @@
+type GHC.Base.MonadPlus :: (* -> *) -> Constraint
class (GHC.Base.Alternative m, GHC.Base.Monad m) =>
- GHC.Base.MonadPlus (m :: * -> *) where
+ GHC.Base.MonadPlus m where
...
mplus :: m a -> m a -> m a
+type GHC.Base.MonadPlus :: (* -> *) -> Constraint
class (GHC.Base.Alternative m, GHC.Base.Monad m) =>
- GHC.Base.MonadPlus (m :: * -> *) where
+ GHC.Base.MonadPlus m where
...
Control.Monad.mplus :: m a -> m a -> m a
diff --git a/testsuite/tests/ghci/scripts/ghci030.stdout b/testsuite/tests/ghci/scripts/ghci030.stdout
index 49ce606456..1195afc37d 100644
--- a/testsuite/tests/ghci/scripts/ghci030.stdout
+++ b/testsuite/tests/ghci/scripts/ghci030.stdout
@@ -1,2 +1,6 @@
-data D = forall a. C (Int -> a) Char -- Defined at ghci030.hs:8:1
-data D = forall a. C (Int -> a) Char -- Defined at ghci030.hs:8:10
+type D :: *
+data D = forall a. C (Int -> a) Char
+ -- Defined at ghci030.hs:8:1
+type D :: *
+data D = forall a. C (Int -> a) Char
+ -- Defined at ghci030.hs:8:10
diff --git a/testsuite/tests/ghci/scripts/ghci031.stdout b/testsuite/tests/ghci/scripts/ghci031.stdout
index 796433e1b7..6ed977034c 100644
--- a/testsuite/tests/ghci/scripts/ghci031.stdout
+++ b/testsuite/tests/ghci/scripts/ghci031.stdout
@@ -1,3 +1,4 @@
type role D nominal
+type D :: * -> *
data Eq a => D a = C a
-- Defined at ghci031.hs:7:1
diff --git a/testsuite/tests/ghci/scripts/ghci033.stdout b/testsuite/tests/ghci/scripts/ghci033.stdout
index e4bfebeb39..4deea62397 100644
--- a/testsuite/tests/ghci/scripts/ghci033.stdout
+++ b/testsuite/tests/ghci/scripts/ghci033.stdout
@@ -1,2 +1,3 @@
+type Foo :: *
data Foo = Foo1 Int | Int `InfixCon` Bool
-- Defined at ghci033.hs:4:1
diff --git a/testsuite/tests/ghci/scripts/ghci040.stdout b/testsuite/tests/ghci/scripts/ghci040.stdout
index d9ebd9c59e..bfd78971a7 100644
--- a/testsuite/tests/ghci/scripts/ghci040.stdout
+++ b/testsuite/tests/ghci/scripts/ghci040.stdout
@@ -1 +1,3 @@
-data Ghci1.T = A | ... -- Defined at <interactive>:2:10
+type Ghci1.T :: *
+data Ghci1.T = A | ...
+ -- Defined at <interactive>:2:10
diff --git a/testsuite/tests/ghci/scripts/ghci041.stdout b/testsuite/tests/ghci/scripts/ghci041.stdout
index 14b8726c76..67a68f00be 100644
--- a/testsuite/tests/ghci/scripts/ghci041.stdout
+++ b/testsuite/tests/ghci/scripts/ghci041.stdout
@@ -1 +1,3 @@
-data R = A | ... -- Defined at <interactive>:3:10
+type R :: *
+data R = A | ...
+ -- Defined at <interactive>:3:10
diff --git a/testsuite/tests/ghci/scripts/ghci042.stdout b/testsuite/tests/ghci/scripts/ghci042.stdout
index 5cb84f632f..d68caeb6b4 100644
--- a/testsuite/tests/ghci/scripts/ghci042.stdout
+++ b/testsuite/tests/ghci/scripts/ghci042.stdout
@@ -1,6 +1,14 @@
-data T = A {...} -- Defined at <interactive>:2:10
-data T = A {a :: Int} -- Defined at <interactive>:2:13
+type T :: *
+data T = A {...}
+ -- Defined at <interactive>:2:10
+type T :: *
+data T = A {a :: Int}
+ -- Defined at <interactive>:2:13
a :: Integer -- Defined at <interactive>:5:5
3
-data R = B {a :: Int} -- Defined at <interactive>:8:13
-data T = A {Ghci1.a :: Int} -- Defined at <interactive>:2:1
+type R :: *
+data R = B {a :: Int}
+ -- Defined at <interactive>:8:13
+type T :: *
+data T = A {Ghci1.a :: Int}
+ -- Defined at <interactive>:2:1
diff --git a/testsuite/tests/ghci/scripts/ghci051.stdout b/testsuite/tests/ghci/scripts/ghci051.stdout
index a3542869a5..9e77b017ba 100644
--- a/testsuite/tests/ghci/scripts/ghci051.stdout
+++ b/testsuite/tests/ghci/scripts/ghci051.stdout
@@ -1,9 +1,21 @@
-data T = C | D -- Defined at <interactive>:8:1
-type T' = Ghci1.T -- Defined at <interactive>:3:1
-data Ghci1.T = A | ... -- Defined at <interactive>:2:10
-data Ghci4.T = B | ... -- Defined at <interactive>:5:12
-data T = C | ... -- Defined at <interactive>:8:14
-data T = ... | D -- Defined at <interactive>:8:18
+type T :: *
+data T = C | D
+ -- Defined at <interactive>:8:1
+type T' :: *
+type T' = Ghci1.T
+ -- Defined at <interactive>:3:1
+type Ghci1.T :: *
+data Ghci1.T = A | ...
+ -- Defined at <interactive>:2:10
+type Ghci4.T :: *
+data Ghci4.T = B | ...
+ -- Defined at <interactive>:5:12
+type T :: *
+data T = C | ...
+ -- Defined at <interactive>:8:14
+type T :: *
+data T = ... | D
+ -- Defined at <interactive>:8:18
b :: T' -- Defined at <interactive>:4:5
c :: Ghci4.T -- Defined at <interactive>:7:5
d :: T -- Defined at <interactive>:9:5
diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout
index 2fc93e6de5..e5cdb3d313 100644
--- a/testsuite/tests/ghci/scripts/ghci059.stdout
+++ b/testsuite/tests/ghci/scripts/ghci059.stdout
@@ -5,6 +5,7 @@ Please see section `The Coercible constraint`
of the user's guide for details.
-}
type role Coercible representational representational
-class Coercible a b => Coercible (a :: k) (b :: k)
+type Coercible :: forall k. k -> k -> Constraint
+class Coercible a b => Coercible a b
-- Defined in ‘GHC.Types’
coerce :: Coercible a b => a -> b -- Defined in ‘GHC.Prim’
diff --git a/testsuite/tests/ghci/should_run/T10145.stdout b/testsuite/tests/ghci/should_run/T10145.stdout
index 4effb90a52..7a949cd465 100644
--- a/testsuite/tests/ghci/should_run/T10145.stdout
+++ b/testsuite/tests/ghci/should_run/T10145.stdout
@@ -1,4 +1,6 @@
-data (->) (a :: TYPE q) (b :: TYPE r) -- Defined in ‘GHC.Prim’
+type (->) :: * -> * -> *
+data (->) a b
+ -- Defined in ‘GHC.Prim’
infixr -1 ->
instance Applicative ((->) r) -- Defined in ‘GHC.Base’
instance Functor ((->) r) -- Defined in ‘GHC.Base’
diff --git a/testsuite/tests/ghci/should_run/T11825.stdout b/testsuite/tests/ghci/should_run/T11825.stdout
index 9ab7b1be0c..6ff7d89cfb 100644
--- a/testsuite/tests/ghci/should_run/T11825.stdout
+++ b/testsuite/tests/ghci/should_run/T11825.stdout
@@ -1,3 +1,4 @@
+type X :: ★ → ★ → Constraint
class X a b | a → b where
to ∷ a → b
{-# MINIMAL to #-}
diff --git a/testsuite/tests/ghci/should_run/T12525.stdout b/testsuite/tests/ghci/should_run/T12525.stdout
index 652a5cdd03..a00ffea4e3 100644
--- a/testsuite/tests/ghci/should_run/T12525.stdout
+++ b/testsuite/tests/ghci/should_run/T12525.stdout
@@ -1,3 +1,4 @@
x :: () = ()
y :: () = ()
+type Foo :: * -> Constraint
class Foo a
diff --git a/testsuite/tests/ghci/should_run/T9914.stdout b/testsuite/tests/ghci/should_run/T9914.stdout
index d9407d3877..5187084e71 100644
--- a/testsuite/tests/ghci/should_run/T9914.stdout
+++ b/testsuite/tests/ghci/should_run/T9914.stdout
@@ -1,5 +1,9 @@
1
2
2
-data T1 = MkT1 -- Defined at <interactive>:6:1
-data T2 = MkT2 -- Defined at <interactive>:8:2
+type T1 :: *
+data T1 = MkT1
+ -- Defined at <interactive>:6:1
+type T2 :: *
+data T2 = MkT2
+ -- Defined at <interactive>:8:2