[commit: ghc] master: Add failing test case for T13611 (1c27e5b)

git at git.haskell.org git at git.haskell.org
Mon Apr 24 17:16:37 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1c27e5b3932cb0b7c3fe2fa3b43a0eae9253b833/ghc

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

commit 1c27e5b3932cb0b7c3fe2fa3b43a0eae9253b833
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Mon Apr 24 13:15:47 2017 -0400

    Add failing test case for T13611
    
    this program should be rejected, but is not (and segfaults).


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

1c27e5b3932cb0b7c3fe2fa3b43a0eae9253b833
 testsuite/tests/typecheck/should_fail/T13611.hs | 9 +++++++++
 testsuite/tests/typecheck/should_fail/all.T     | 1 +
 2 files changed, 10 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/T13611.hs b/testsuite/tests/typecheck/should_fail/T13611.hs
new file mode 100644
index 0000000..ea22791
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T13611.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+import GHC.Prim
+import GHC.Types
+
+main = do
+    let local = ()
+    let null = 0## :: Word#
+    let triple = (# local, null, null #)
+    IO (\s -> case mkWeakNoFinalizer# triple () s of (# s, r #) -> (# s, () #))
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index c8d5869..8bbb671 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -434,3 +434,4 @@ test('T13300', normal, compile_fail, [''])
 test('T12709', normal, compile_fail, [''])
 test('T13446', normal, compile_fail, [''])
 test('T13506', normal, compile_fail, [''])
+test('T13611', expect_broken(13611), compile_fail, [''])



More information about the ghc-commits mailing list