[commit: testsuite] master: Add regression test for #8103 (e8e88fe)

git at git.haskell.org git at git.haskell.org
Wed Aug 14 17:59:50 CEST 2013


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

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

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

commit e8e88fe308720c7b7e8e3ba3e103ba22acd27b5b
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Wed Aug 14 16:34:06 2013 +0100

    Add regression test for #8103


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

e8e88fe308720c7b7e8e3ba3e103ba22acd27b5b
 tests/codeGen/should_run/T8103.hs                       |    8 ++++++++
 tests/codeGen/should_run/{T2838.stdout => T8103.stdout} |    0
 tests/codeGen/should_run/T8103_A.hs                     |    7 +++++++
 tests/codeGen/should_run/all.T                          |    2 +-
 4 files changed, 16 insertions(+), 1 deletion(-)

diff --git a/tests/codeGen/should_run/T8103.hs b/tests/codeGen/should_run/T8103.hs
new file mode 100644
index 0000000..99e213b
--- /dev/null
+++ b/tests/codeGen/should_run/T8103.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE MagicHash #-}
+module Main where
+import T8103_A
+
+float_text = case (0.0## `foo` 1.2##) of
+               0.0## -> "1"
+               _     -> "0"
+main = putStrLn (float_text)
diff --git a/tests/codeGen/should_run/T2838.stdout b/tests/codeGen/should_run/T8103.stdout
similarity index 100%
copy from tests/codeGen/should_run/T2838.stdout
copy to tests/codeGen/should_run/T8103.stdout
diff --git a/tests/codeGen/should_run/T8103_A.hs b/tests/codeGen/should_run/T8103_A.hs
new file mode 100644
index 0000000..0e450d4
--- /dev/null
+++ b/tests/codeGen/should_run/T8103_A.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE MagicHash #-}
+module T8103_A where
+import GHC.Exts
+
+{-# NOINLINE foo #-}
+foo  :: Double# -> Double# -> Double#
+foo a b = (a +## b)
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index e18bfa6..88095f0 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -112,4 +112,4 @@ test('Word2Float64', unless(wordsize(64), skip), compile_and_run, [''])
 
 test('T7361', normal, compile_and_run, [''])
 test('T7600', normal, compile_and_run, [''])
-
+test('T8103', only_ways(['normal']), compile_and_run, [''])





More information about the ghc-commits mailing list