[commit: ghc] master: Add testcase for #12757 (b5460dd)

git at git.haskell.org git at git.haskell.org
Thu Nov 3 02:43:10 UTC 2016


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

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

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

commit b5460dd6e54f4ba54bfb11469221e8c8f957e964
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Wed Nov 2 17:02:14 2016 -0400

    Add testcase for #12757
    
    Test Plan: Validate, expected to fail
    
    Reviewers: austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2665
    
    GHC Trac Issues: #12757


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

b5460dd6e54f4ba54bfb11469221e8c8f957e964
 testsuite/tests/codeGen/should_run/T12757.hs       | 28 ++++++++++++++++++++++
 .../should_run/T12757.stdout}                      |  2 +-
 testsuite/tests/codeGen/should_run/all.T           |  1 +
 3 files changed, 30 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/codeGen/should_run/T12757.hs b/testsuite/tests/codeGen/should_run/T12757.hs
new file mode 100644
index 0000000..148fe7a
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T12757.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Main (main) where
+
+import           Data.ByteString        (ByteString)
+import qualified Data.ByteString        as B
+
+answers :: [ByteString]
+answers = map (B.filter (/= 0x20))
+    [ "e3b0c442 98fc1c14 9afbf4c8 996fb924 27ae41e4 649b934c a495991b 7852b855"
+    , "d7a8fbb3 07d78094 69ca9abc b0082e4f 8d5651e4 6d3cdb76 2d02d0bf 37c9e592"
+    , "e4c4d8f3 bf76b692 de791a17 3e053211 50f7a345 b46484fe 427f6acc 7ecc81be"
+    , "ba7816bf 8f01cfea 414140de 5dae2223 b00361a3 96177a9c b410ff61 f20015ad"
+    , "248d6a61 d20638b8 e5c02693 0c3e6039 a33ce459 64ff2167 f6ecedd4 19db06c1"
+    , "cf5b16a7 78af8380 036ce59e 7b049237 0b249b11 e8f07a51 afac4503 7afee9d1"
+    , "cdc76e5c 9914fb92 81a1c7e2 84d73e67 f1809a48 a497200e 046d39cc c7112cd0"
+    ]
+
+x, y :: ByteString
+x = "e3b0c442 98fc1c14 9afbf4c8 996fb924 27ae41e4 649b934c a495991b 7852b855"
+y = B.filter (/= 0x20) x
+
+main :: IO ()
+main = do
+    print (seq x ())
+    print (seq y ())
+    print (length answers)
+    print (seq (head answers) ()) -- segfault!
diff --git a/testsuite/tests/deriving/should_run/T3087.stdout b/testsuite/tests/codeGen/should_run/T12757.stdout
similarity index 75%
copy from testsuite/tests/deriving/should_run/T3087.stdout
copy to testsuite/tests/codeGen/should_run/T12757.stdout
index 35735b4..0c66d1a 100644
--- a/testsuite/tests/deriving/should_run/T3087.stdout
+++ b/testsuite/tests/codeGen/should_run/T12757.stdout
@@ -1,4 +1,4 @@
 ()
 ()
-()
+7
 ()
diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T
index 23caa8c..4e68448 100644
--- a/testsuite/tests/codeGen/should_run/all.T
+++ b/testsuite/tests/codeGen/should_run/all.T
@@ -146,3 +146,4 @@ test('PopCnt', omit_ways(['ghci']), multi_compile_and_run,
                  ['PopCnt', [('PopCnt_cmm.cmm', '')], ''])
 test('T12059', normal, compile_and_run, [''])
 test('T12433', normal, compile_and_run, [''])
+test('T12757', normal, compile_and_run, [''])



More information about the ghc-commits mailing list