[commit: testsuite] master: Test Trac #7477 (37158ff)

git at git.haskell.org git at git.haskell.org
Wed Nov 6 10:40:22 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/37158ff9ee3603c863eee8dcdfd196750fe8847a/testsuite

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

commit 37158ff9ee3603c863eee8dcdfd196750fe8847a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Nov 6 09:34:03 2013 +0000

    Test Trac #7477


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

37158ff9ee3603c863eee8dcdfd196750fe8847a
 tests/th/T7477.hs                                |   12 ++++++++++++
 tests/{ghci/linking/T3333.hs => th/T7477.stderr} |    6 ++----
 tests/th/all.T                                   |    1 +
 3 files changed, 15 insertions(+), 4 deletions(-)

diff --git a/tests/th/T7477.hs b/tests/th/T7477.hs
new file mode 100644
index 0000000..4e4d018
--- /dev/null
+++ b/tests/th/T7477.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds, KindSignatures, PolyKinds, TypeFamilies, TemplateHaskell #-}
+
+module T7477 where
+
+import Language.Haskell.TH
+
+type family F (a :: k)
+type instance F Int = Bool
+
+$( do { info <- reifyInstances ''F [ConT ''Int]
+      ; reportWarning (pprint info)
+      ; return [] })
diff --git a/tests/ghci/linking/T3333.hs b/tests/th/T7477.stderr
similarity index 52%
copy from tests/ghci/linking/T3333.hs
copy to tests/th/T7477.stderr
index 82c8909..f6a9e0d 100644
--- a/tests/ghci/linking/T3333.hs
+++ b/tests/th/T7477.stderr
@@ -1,5 +1,3 @@
-module WeakTest where
 
-import Foreign.C.Types
-
-foreign import ccall weak_test :: CInt -> IO CInt
+T7477.hs:10:4: Warning:
+    type instance T7477.F GHC.Prim.* GHC.Types.Int = GHC.Types.Bool
diff --git a/tests/th/all.T b/tests/th/all.T
index 55c5a93..9b959fa 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -304,3 +304,4 @@ test('T7667', normal, compile, ['-v0'])
 test('T7667a', normal, compile_fail, ['-v0'])
 test('T8455', normal, compile, ['-v0'])
 test('T8499', normal, compile, ['-v0'])
+test('T7477', normal, compile, ['-v0'])



More information about the ghc-commits mailing list