[commit: testsuite] master: Test Trac #8037 (9441b7f)

git at git.haskell.org git at git.haskell.org
Fri Nov 8 10:52:32 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/9441b7fbf952adf9a3a4402167ba40d8d2166d98/testsuite

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

commit 9441b7fbf952adf9a3a4402167ba40d8d2166d98
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Nov 8 10:52:14 2013 +0000

    Test Trac #8037


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

9441b7fbf952adf9a3a4402167ba40d8d2166d98
 tests/stranal/should_compile/T8037.hs |   17 +++++++++++++++++
 tests/stranal/should_compile/all.T    |    1 +
 2 files changed, 18 insertions(+)

diff --git a/tests/stranal/should_compile/T8037.hs b/tests/stranal/should_compile/T8037.hs
new file mode 100644
index 0000000..62d2a13
--- /dev/null
+++ b/tests/stranal/should_compile/T8037.hs
@@ -0,0 +1,17 @@
+module T8037 where
+
+import Unsafe.Coerce
+import Foreign.C.Types
+import System.IO.Unsafe
+
+data D4 = D4 CInt CInt CInt
+data Color3 = Color3 CInt CInt
+
+crash :: D4 -> IO ()
+crash x = color (unsafeCoerce x)
+
+color :: Color3 -> IO ()
+color (Color3 r g) = f (unsafePerformIO undefined) r g
+
+foreign import ccall f :: CInt -> CInt -> CInt -> IO ()
+
diff --git a/tests/stranal/should_compile/all.T b/tests/stranal/should_compile/all.T
index 9467a7e..7ee45ad 100644
--- a/tests/stranal/should_compile/all.T
+++ b/tests/stranal/should_compile/all.T
@@ -17,3 +17,4 @@ test('unu', normal, compile, [''])
 test('newtype', req_profiling, compile, ['-prof -auto-all'])
 test('T1988', normal, compile, [''])
 test('T8467', normal, compile, [''])
+test('T8037', normal, compile, [''])



More information about the ghc-commits mailing list