[commit: ghc] wip/angerman/llvmng: Adds test (561da2a)

git at git.haskell.org git at git.haskell.org
Thu Sep 28 03:12:22 UTC 2017


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

On branch  : wip/angerman/llvmng
Link       : http://ghc.haskell.org/trac/ghc/changeset/561da2aa8657454efd4bf86ed53da112a7bc0cdb/ghc

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

commit 561da2aa8657454efd4bf86ed53da112a7bc0cdb
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date:   Thu Sep 21 22:07:44 2017 +0800

    Adds test


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

561da2aa8657454efd4bf86ed53da112a7bc0cdb
 testsuite/tests/codeGen/should_run/T14251.hs     | 22 ++++++++++++++++++++++
 testsuite/tests/codeGen/should_run/T14251.stdout |  1 +
 testsuite/tests/codeGen/should_run/all.T         |  1 +
 3 files changed, 24 insertions(+)

diff --git a/testsuite/tests/codeGen/should_run/T14251.hs b/testsuite/tests/codeGen/should_run/T14251.hs
new file mode 100644
index 0000000..6f552e1
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T14251.hs
@@ -0,0 +1,22 @@
+{-# LANGUAGE MagicHash, BangPatterns #-}
+module Main where
+
+-- A minor modification from T8064.hs.
+--
+-- The key here is that we ensure that
+-- subsequently passed floats do not
+-- accidentally end up in previous
+-- registers.
+--
+
+import GHC.Exts
+
+{-# NOINLINE f #-}
+f :: (Int# -> Float# -> Double# -> Float# -> Double# -> String) -> String
+f g = g 3# 4.0# 5.0## 6.0# 6.9## ++ " World!"
+
+{-# NOINLINE q #-}
+q :: Int# -> Float# -> Double# -> Float# -> Double# -> String
+q i j k l m = "Hello " ++ show (F# l) ++ " " ++ show (D# m)
+
+main = putStrLn (f $ q)
diff --git a/testsuite/tests/codeGen/should_run/T14251.stdout b/testsuite/tests/codeGen/should_run/T14251.stdout
new file mode 100644
index 0000000..8ec577b
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T14251.stdout
@@ -0,0 +1 @@
+Hello 6.0 6.9 World!
diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T
index 271a420..36e4855 100644
--- a/testsuite/tests/codeGen/should_run/all.T
+++ b/testsuite/tests/codeGen/should_run/all.T
@@ -158,3 +158,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip),
 
 test('T13425', normal, compile_and_run, ['-O'])
 test('castFloatWord', normal, compile_and_run, ['-dcmm-lint'])
+test('T14251', normal, compile_and_run, ['-O2'])



More information about the ghc-commits mailing list