[commit: testsuite] master: Test #7710 (572cd70)
José Pedro Magalhães
jpm at cs.uu.nl
Thu Feb 21 11:29:23 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/572cd7091e7e2eee8475432cb0a356e5357269d3
>---------------------------------------------------------------
commit 572cd7091e7e2eee8475432cb0a356e5357269d3
Author: Jose Pedro Magalhaes <jpm at cs.ox.ac.uk>
Date: Thu Feb 21 09:40:47 2013 +0000
Test #7710
>---------------------------------------------------------------
tests/deriving/should_compile/T7710.hs | 21 +++++++++++++++++++++
tests/deriving/should_compile/all.T | 1 +
2 files changed, 22 insertions(+), 0 deletions(-)
diff --git a/tests/deriving/should_compile/T7710.hs b/tests/deriving/should_compile/T7710.hs
new file mode 100644
index 0000000..5375c2c
--- /dev/null
+++ b/tests/deriving/should_compile/T7710.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE AutoDeriveTypeable #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module T7710 where
+
+import Data.Typeable
+
+
+type T = Int
+type family F a
+type instance F Int = Int
+data family D a
+data instance D Int = DInt
+data instance D Float = DFloat
+
+test = [ typeRep ([] :: [T])
+ , typeRep ([] :: [F Int])
+ , typeRep (Proxy :: Proxy D)
+ , typeRep ([] :: [D Int]) ]
diff --git a/tests/deriving/should_compile/all.T b/tests/deriving/should_compile/all.T
index 5e9af5e..b2355f6 100644
--- a/tests/deriving/should_compile/all.T
+++ b/tests/deriving/should_compile/all.T
@@ -36,3 +36,4 @@ test('T1133',
extra_clean(['T1133.o-boot', 'T1133.hi-boot']),
run_command,
['$MAKE --no-print-directory -s T1133'])
+test('T7710', normal, compile, [''])
\ No newline at end of file
More information about the ghc-commits
mailing list