[commit: ghc] master: Add failing test for #9562. (23582b0)
git at git.haskell.org
git at git.haskell.org
Thu Jun 11 21:57:47 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/23582b0c16bb147dad6bd7dee98686a8b61eacea/ghc
>---------------------------------------------------------------
commit 23582b0c16bb147dad6bd7dee98686a8b61eacea
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date: Thu Jun 11 14:57:50 2015 -0700
Add failing test for #9562.
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
>---------------------------------------------------------------
23582b0c16bb147dad6bd7dee98686a8b61eacea
testsuite/.gitignore | 1 +
testsuite/tests/driver/T9562/A.hs | 5 +++++
testsuite/tests/driver/T9562/B.hs | 11 +++++++++++
.../tests/{ghci/prog010/B.hs => driver/T9562/B.hs-boot} | 2 ++
.../scripts/break023/A1.hs => driver/T9562/C.hs} | 3 ++-
testsuite/tests/driver/T9562/D.hs | 11 +++++++++++
testsuite/tests/driver/T9562/Main.hs | 5 +++++
testsuite/tests/driver/T9562/Makefile | 12 ++++++++++++
testsuite/tests/driver/T9562/all.T | 6 ++++++
9 files changed, 55 insertions(+), 1 deletion(-)
diff --git a/testsuite/.gitignore b/testsuite/.gitignore
index 1855727..ade0024 100644
--- a/testsuite/.gitignore
+++ b/testsuite/.gitignore
@@ -540,6 +540,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk
/tests/driver/T7835/Test
/tests/driver/T8526/A.inc
/tests/driver/T8602/t8602.sh
+/tests/driver/T9562/Main
/tests/driver/Test.081b
/tests/driver/Test.081b.hs
/tests/driver/Test_081a
diff --git a/testsuite/tests/driver/T9562/A.hs b/testsuite/tests/driver/T9562/A.hs
new file mode 100644
index 0000000..03f5ad3
--- /dev/null
+++ b/testsuite/tests/driver/T9562/A.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module A where
+
+type family F a b
diff --git a/testsuite/tests/driver/T9562/B.hs b/testsuite/tests/driver/T9562/B.hs
new file mode 100644
index 0000000..34fe7b8
--- /dev/null
+++ b/testsuite/tests/driver/T9562/B.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module B where
+
+import A
+import C
+
+type instance F a b = b
+
+oops :: F a b -> a -> b
+oops = const
diff --git a/testsuite/tests/ghci/prog010/B.hs b/testsuite/tests/driver/T9562/B.hs-boot
similarity index 50%
copy from testsuite/tests/ghci/prog010/B.hs
copy to testsuite/tests/driver/T9562/B.hs-boot
index ce9e7e4..facbc8c 100644
--- a/testsuite/tests/ghci/prog010/B.hs
+++ b/testsuite/tests/driver/T9562/B.hs-boot
@@ -1,3 +1,5 @@
module B where
import A
+
+oops :: F a b -> a -> b
diff --git a/testsuite/tests/ghci.debugger/scripts/break023/A1.hs b/testsuite/tests/driver/T9562/C.hs
similarity index 51%
copy from testsuite/tests/ghci.debugger/scripts/break023/A1.hs
copy to testsuite/tests/driver/T9562/C.hs
index 138a4fa..bca4f46 100644
--- a/testsuite/tests/ghci.debugger/scripts/break023/A1.hs
+++ b/testsuite/tests/driver/T9562/C.hs
@@ -1,2 +1,3 @@
-module A where
+module C (oops) where
+
import {-# SOURCE #-} B
diff --git a/testsuite/tests/driver/T9562/D.hs b/testsuite/tests/driver/T9562/D.hs
new file mode 100644
index 0000000..c9beceb
--- /dev/null
+++ b/testsuite/tests/driver/T9562/D.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module D where
+
+import A
+import C
+
+type instance F a b = a
+
+unsafeCoerce :: a -> b
+unsafeCoerce x = oops x x
diff --git a/testsuite/tests/driver/T9562/Main.hs b/testsuite/tests/driver/T9562/Main.hs
new file mode 100644
index 0000000..fabf5f5
--- /dev/null
+++ b/testsuite/tests/driver/T9562/Main.hs
@@ -0,0 +1,5 @@
+module Main where
+
+import D ( unsafeCoerce )
+
+main = print $ (unsafeCoerce True :: Int)
diff --git a/testsuite/tests/driver/T9562/Makefile b/testsuite/tests/driver/T9562/Makefile
new file mode 100644
index 0000000..423389d
--- /dev/null
+++ b/testsuite/tests/driver/T9562/Makefile
@@ -0,0 +1,12 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T9562:
+ rm -f *.o *.hi *.o-boot *.hi-boot Main
+ '$(TEST_HC)' -c A.hs
+ '$(TEST_HC)' -c B.hs-boot
+ '$(TEST_HC)' -c C.hs
+ '$(TEST_HC)' -c B.hs
+ '$(TEST_HC)' -c D.hs
+ ! ('$(TEST_HC)' Main.hs && ./Main)
diff --git a/testsuite/tests/driver/T9562/all.T b/testsuite/tests/driver/T9562/all.T
new file mode 100644
index 0000000..ab379ee
--- /dev/null
+++ b/testsuite/tests/driver/T9562/all.T
@@ -0,0 +1,6 @@
+setTestOpts(only_compiler_types(['ghc']))
+
+test('T9562',
+ [extra_clean(['A011.hi', 'A011.o']), expect_broken(9562)],
+ run_command,
+ ['$MAKE -s --no-print-directory T9562'])
More information about the ghc-commits
mailing list