[commit: testsuite] master: Initial test for Trac #4175 (886872b)
Simon Peyton Jones
simonpj at microsoft.com
Fri Mar 15 16:54:51 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/886872b78fa9d5ee56eea850a75824c8752b3237
>---------------------------------------------------------------
commit 886872b78fa9d5ee56eea850a75824c8752b3237
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Mar 15 15:53:34 2013 +0000
Initial test for Trac #4175
>---------------------------------------------------------------
tests/ghci/scripts/T4175.hs | 24 ++++++++++++++++++
tests/ghci/scripts/T4175.script | 8 ++++++
tests/ghci/scripts/T4175.stdout | 52 +++++++++++++++++++++++++++++++++++++++
3 files changed, 84 insertions(+), 0 deletions(-)
diff --git a/tests/ghci/scripts/T4175.hs b/tests/ghci/scripts/T4175.hs
new file mode 100644
index 0000000..69ff79f
--- /dev/null
+++ b/tests/ghci/scripts/T4175.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE TypeFamilies #-}
+module T4175 where
+
+type family A a b
+type instance A Int Int = ()
+type instance A (Maybe a) a = a
+
+data family B a
+data instance B () = MkB
+
+class C a where
+ type D a b
+
+instance C Int where
+ type D Int () = String
+
+instance C () where
+ type D () () = Bool
+
+type family E a
+
+type instance where
+ E () = Bool
+ E Int = String
\ No newline at end of file
diff --git a/tests/ghci/scripts/T4175.script b/tests/ghci/scripts/T4175.script
new file mode 100644
index 0000000..27410d7
--- /dev/null
+++ b/tests/ghci/scripts/T4175.script
@@ -0,0 +1,8 @@
+:l T4175.hs
+:i A
+:i B
+:i D
+:i E
+:i ()
+:i Maybe
+:i Int
diff --git a/tests/ghci/scripts/T4175.stdout b/tests/ghci/scripts/T4175.stdout
new file mode 100644
index 0000000..bfbfc87
--- /dev/null
+++ b/tests/ghci/scripts/T4175.stdout
@@ -0,0 +1,52 @@
+type family A a b :: * -- Defined at T4175.hs:4:13
+type instance A (Maybe a) a -- Defined at T4175.hs:6:15
+type instance A Int Int -- Defined at T4175.hs:5:15
+data family B a -- Defined at T4175.hs:8:13
+data instance B () -- Defined at T4175.hs:9:15
+class C a where
+ type family D a b :: *
+ -- Defined at T4175.hs:12:10
+type D () () -- Defined at T4175.hs:18:10
+type D Int () -- Defined at T4175.hs:15:10
+type family E a :: * -- Defined at T4175.hs:20:13
+type instance where
+ E () -- Defined at T4175.hs:23:5
+ E Int -- Defined at T4175.hs:24:5
+data () = () -- Defined in âGHC.Tupleâ
+instance C () -- Defined at T4175.hs:17: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 instance where
+ E () -- Defined at T4175.hs:23:5
+ E Int -- Defined at T4175.hs:24:5
+type D () () -- Defined at T4175.hs:18:10
+type D Int () -- Defined at T4175.hs:15:10
+data instance B () -- Defined at T4175.hs:9: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â
+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:15
+data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in âGHC.Typesâ
+instance C Int -- Defined at T4175.hs:14:10
+instance Bounded Int -- Defined in âGHC.Enumâ
+instance Enum Int -- Defined in âGHC.Enumâ
+instance Eq Int -- Defined in âGHC.Classesâ
+instance Integral Int -- Defined in âGHC.Realâ
+instance Num Int -- Defined in âGHC.Numâ
+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 instance where
+ E () -- Defined at T4175.hs:23:5
+ E Int -- Defined at T4175.hs:24:5
+type D Int () -- Defined at T4175.hs:15:10
+type instance A Int Int -- Defined at T4175.hs:5:15
More information about the ghc-commits
mailing list