Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/a443715e79d6713cc0a9d9d36713e8c891b87079

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

commit a443715e79d6713cc0a9d9d36713e8c891b87079
Author: Simon Marlow <marlo...@gmail.com>
Date:   Wed Jan 9 16:51:19 2013 +0000

    Add test for #7361

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

 tests/codeGen/should_run/T7361.hs     |   12 ++++++++++++
 tests/codeGen/should_run/T7361.stdout |    1 +
 tests/codeGen/should_run/all.T        |    2 ++
 3 files changed, 15 insertions(+), 0 deletions(-)

diff --git a/tests/codeGen/should_run/T7361.hs 
b/tests/codeGen/should_run/T7361.hs
new file mode 100644
index 0000000..81301e4
--- /dev/null
+++ b/tests/codeGen/should_run/T7361.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE MagicHash #-}
+import GHC.Exts
+
+main = print $ map f [1,256,65536,minBound,maxBound]
+
+f (I# x#) =
+      [ I# (narrow8Int#  (narrow16Int# x#))
+      , I# (narrow8Int#  (narrow32Int# x#))
+      , I# (narrow16Int# (narrow8Int#  x#))
+      , I# (narrow16Int# (narrow32Int# x#))
+      , I# (narrow32Int# (narrow8Int#  x#))
+      , I# (narrow32Int# (narrow16Int# x#))]
diff --git a/tests/codeGen/should_run/T7361.stdout 
b/tests/codeGen/should_run/T7361.stdout
new file mode 100644
index 0000000..3b6bc30
--- /dev/null
+++ b/tests/codeGen/should_run/T7361.stdout
@@ -0,0 +1 @@
+[[1,1,1,1,1,1],[0,0,0,256,0,256],[0,0,0,0,0,0],[0,0,0,0,0,0],[-1,-1,-1,-1,-1,-1]]
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index 1a5733d..456f2c2 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -102,3 +102,5 @@ test('T7319', [ extra_ways(['prof']), only_ways(['prof']), 
exit_code(1),
                 extra_run_opts('+RTS -xc') ], compile_and_run, [''])
 test('Word2Float32', unless_wordsize(32, skip), compile_and_run, [''])
 test('Word2Float64', unless_wordsize(64, skip), compile_and_run, [''])
+
+test('T7361', normal, compile_and_run, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to