[commit: testsuite] master: Increase coverage of #4175 (3d6deba)
git at git.haskell.org
git at git.haskell.org
Fri Nov 15 00:40:47 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3d6debaa48f48812878e8f66cc64c49b1fb81d35/testsuite
>---------------------------------------------------------------
commit 3d6debaa48f48812878e8f66cc64c49b1fb81d35
Author: Patrick Palka <patrick at parcs.ath.cx>
Date: Thu Nov 14 18:14:15 2013 -0500
Increase coverage of #4175
>---------------------------------------------------------------
3d6debaa48f48812878e8f66cc64c49b1fb81d35
tests/ghci/scripts/T4175.hs | 12 ++++++++++++
tests/ghci/scripts/T4175.script | 1 +
tests/ghci/scripts/T4175.stdout | 41 ++++++++++++++++++++++-----------------
3 files changed, 36 insertions(+), 18 deletions(-)
diff --git a/tests/ghci/scripts/T4175.hs b/tests/ghci/scripts/T4175.hs
index a3b1d27..0fc53e7 100644
--- a/tests/ghci/scripts/T4175.hs
+++ b/tests/ghci/scripts/T4175.hs
@@ -1,9 +1,13 @@
{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE ConstraintKinds #-}
module T4175 where
+import GHC.Exts
+
type family A a b
type instance A Int Int = ()
type instance A (Maybe a) a = a
+type instance A (B a) b = ()
data family B a
data instance B () = MkB
@@ -20,3 +24,11 @@ instance C () where
type family E a where
E () = Bool
E Int = String
+
+class Z a
+
+class F (a :: Constraint)
+instance F (Z a)
+
+class G (a :: * -> *)
+instance G B
diff --git a/tests/ghci/scripts/T4175.script b/tests/ghci/scripts/T4175.script
index 27410d7..3a8588e 100644
--- a/tests/ghci/scripts/T4175.script
+++ b/tests/ghci/scripts/T4175.script
@@ -6,3 +6,4 @@
:i ()
:i Maybe
:i Int
+:i Z
diff --git a/tests/ghci/scripts/T4175.stdout b/tests/ghci/scripts/T4175.stdout
index c631189..d8b8de0 100644
--- a/tests/ghci/scripts/T4175.stdout
+++ b/tests/ghci/scripts/T4175.stdout
@@ -1,30 +1,33 @@
-type family A a b :: * -- Defined at T4175.hs:4:1
-type instance A (Maybe a) a -- Defined at T4175.hs:6:1
-type instance A Int Int -- Defined at T4175.hs:5:1
+type family A a b :: * -- Defined at T4175.hs:7:1
+type instance A (B a) b -- Defined at T4175.hs:10:1
+type instance A (Maybe a) a -- Defined at T4175.hs:9:1
+type instance A Int Int -- Defined at T4175.hs:8:1
type role B nominal
data family B a
- -- Defined at T4175.hs:8:1
-data instance B () -- Defined at T4175.hs:9:15
+ -- Defined at T4175.hs:12:1
+instance G B -- Defined at T4175.hs:34:10
+data instance B () -- Defined at T4175.hs:13:15
+type instance A (B a) b -- Defined at T4175.hs:10:1
class C a where
type family D a b :: *
- -- Defined at T4175.hs:12:5
-type D () () -- Defined at T4175.hs:18:5
-type D Int () -- Defined at T4175.hs:15:5
+ -- Defined at T4175.hs:16:5
+type D () () -- Defined at T4175.hs:22:5
+type D Int () -- Defined at T4175.hs:19:5
type family E a :: * where
E () = Bool
E Int = String
- -- Defined at T4175.hs:20:1
+ -- Defined at T4175.hs:24:1
data () = () -- Defined in ‛GHC.Tuple’
-instance C () -- Defined at T4175.hs:17:10
+instance C () -- Defined at T4175.hs:21:10
instance Bounded () -- Defined in ‛GHC.Enum’
instance Enum () -- Defined in ‛GHC.Enum’
instance Eq () -- Defined in ‛GHC.Classes’
instance Ord () -- Defined in ‛GHC.Classes’
instance Read () -- Defined in ‛GHC.Read’
instance Show () -- Defined in ‛GHC.Show’
-type D () () -- Defined at T4175.hs:18:5
-type D Int () -- Defined at T4175.hs:15:5
-data instance B () -- Defined at T4175.hs:9:15
+type D () () -- Defined at T4175.hs:22:5
+type D Int () -- Defined at T4175.hs:19:5
+data instance B () -- Defined at T4175.hs:13:15
data Maybe a = Nothing | Just a -- Defined in ‛Data.Maybe’
instance Eq a => Eq (Maybe a) -- Defined in ‛Data.Maybe’
instance Monad Maybe -- Defined in ‛Data.Maybe’
@@ -32,9 +35,9 @@ instance Functor Maybe -- Defined in ‛Data.Maybe’
instance Ord a => Ord (Maybe a) -- Defined in ‛Data.Maybe’
instance Read a => Read (Maybe a) -- Defined in ‛GHC.Read’
instance Show a => Show (Maybe a) -- Defined in ‛GHC.Show’
-type instance A (Maybe a) a -- Defined at T4175.hs:6:1
-data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‛GHC.Types’
-instance C Int -- Defined at T4175.hs:14:10
+type instance A (Maybe a) a -- Defined at T4175.hs:9:1
+data Int = I# Int# -- Defined in ‛GHC.Types’
+instance C Int -- Defined at T4175.hs:18:10
instance Bounded Int -- Defined in ‛GHC.Enum’
instance Enum Int -- Defined in ‛GHC.Enum’
instance Eq Int -- Defined in ‛GHC.Classes’
@@ -44,5 +47,7 @@ instance Ord Int -- Defined in ‛GHC.Classes’
instance Read Int -- Defined in ‛GHC.Read’
instance Real Int -- Defined in ‛GHC.Real’
instance Show Int -- Defined in ‛GHC.Show’
-type D Int () -- Defined at T4175.hs:15:5
-type instance A Int Int -- Defined at T4175.hs:5:1
+type D Int () -- Defined at T4175.hs:19:5
+type instance A Int Int -- Defined at T4175.hs:8:1
+class Z a -- Defined at T4175.hs:28:1
+instance F (Z a) -- Defined at T4175.hs:31:10
More information about the ghc-commits
mailing list