[commit: ghc] master: Fix tests due to issue #7021 (182ff9e)

git at git.haskell.org git at git.haskell.org
Mon Feb 10 01:39:30 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/182ff9e814a917681b1600b2729c3340801630de/ghc

>---------------------------------------------------------------

commit 182ff9e814a917681b1600b2729c3340801630de
Author: YoEight <yo.eight at gmail.com>
Date:   Sat Jan 11 13:47:24 2014 +0100

    Fix tests due to issue #7021
    
    Signed-off-by: Richard Eisenberg <eir at cis.upenn.edu>


>---------------------------------------------------------------

182ff9e814a917681b1600b2729c3340801630de
 testsuite/tests/th/T7021.hs       |    7 +++++++
 testsuite/tests/th/T7021a.hs      |   31 +++++++++++++++++++++++++++++++
 testsuite/tests/th/TH_genExLib.hs |    2 +-
 3 files changed, 39 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/th/T7021.hs b/testsuite/tests/th/T7021.hs
new file mode 100644
index 0000000..31e1843
--- /dev/null
+++ b/testsuite/tests/th/T7021.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T7021 where
+
+import T7021a
+
+func :: a -> Int
+func = $(test)
diff --git a/testsuite/tests/th/T7021a.hs b/testsuite/tests/th/T7021a.hs
new file mode 100644
index 0000000..bd19133
--- /dev/null
+++ b/testsuite/tests/th/T7021a.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE ConstraintKinds, TemplateHaskell, PolyKinds, TypeFamilies #-}
+
+module T7021a where
+
+import GHC.Prim
+import Language.Haskell.TH
+
+type IOable a = (Show a, Read a)
+type family ALittleSilly :: Constraint
+
+data Proxy a = Proxy
+
+foo :: IOable a => a
+foo = undefined
+
+baz :: a b => Proxy a -> b
+baz = undefined
+
+bar :: ALittleSilly  => a
+bar = undefined
+
+test :: Q Exp
+test = do
+    Just fooName <- lookupValueName "foo"
+    Just bazName <- lookupValueName "baz"
+    Just barName <- lookupValueName "bar"
+    reify fooName
+    reify bazName
+    reify barName
+    [t| (Show a, (Read a, Num a)) => a -> a |]
+    [| \_ -> 0 |]
diff --git a/testsuite/tests/th/TH_genExLib.hs b/testsuite/tests/th/TH_genExLib.hs
index 02784ac..d439231 100644
--- a/testsuite/tests/th/TH_genExLib.hs
+++ b/testsuite/tests/th/TH_genExLib.hs
@@ -15,6 +15,6 @@ genAnyClass name decls
   = DataD [] anyName [] [constructor] []
   where
     anyName = mkName ("Any" ++ nameBase name ++ "1111")
-    constructor = ForallC [PlainTV var_a] [ClassP name [VarT var_a]] $
+    constructor = ForallC [PlainTV var_a] [AppT (ConT name) (VarT var_a)] $
 		  NormalC anyName [(NotStrict, VarT var_a)]
     var_a = mkName "a"



More information about the ghc-commits mailing list