[commit: testsuite] master: Add test for T6084 (3d9ebe9)

git at git.haskell.org git at git.haskell.org
Thu Nov 28 12:53:35 UTC 2013


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

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

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

commit 3d9ebe96080347dcf40621c895ca6af708d66c64
Author: Simon Marlow <marlowsd at gmail.com>
Date:   Thu Nov 28 11:32:52 2013 +0000

    Add test for T6084


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

3d9ebe96080347dcf40621c895ca6af708d66c64
 tests/codeGen/should_run/T6084.hs     |   28 ++++++++++++++++++++++++++++
 tests/codeGen/should_run/T6084.stdout |    3 +++
 tests/codeGen/should_run/all.T        |    1 +
 3 files changed, 32 insertions(+)

diff --git a/tests/codeGen/should_run/T6084.hs b/tests/codeGen/should_run/T6084.hs
new file mode 100644
index 0000000..166dd39
--- /dev/null
+++ b/tests/codeGen/should_run/T6084.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE MagicHash, BangPatterns #-}
+module Main where
+
+import GHC.Exts
+
+{-# NOINLINE f #-}
+f :: (Int# -> Float# -> Double# -> String) -> String
+f g = g 3# 4.0# 6.9## ++ " World!"
+
+{-# NOINLINE p #-}
+p :: Int# -> Float# -> Double# -> String
+p i j k = "Hello"
+
+{-# NOINLINE q #-}
+q :: Int# -> Int# -> Float# -> Double# -> String
+q _ i j k = "Hello"
+
+{-# NOINLINE r #-}
+r :: Int# -> Float# -> Double# -> String
+r i = let !(I# z) = length [I# 1# .. I# i] in \j k -> p z j k
+  -- ghc won't eta-expand around the length, because it has unknown cost
+
+main = do
+  putStrLn (f p)    -- fast call
+  putStrLn (f r)    -- slow call: function but wrong arity
+  let g = last [q 1#]
+  putStrLn (f g)    -- slow call: thunk
+
diff --git a/tests/codeGen/should_run/T6084.stdout b/tests/codeGen/should_run/T6084.stdout
new file mode 100644
index 0000000..8baa6e3
--- /dev/null
+++ b/tests/codeGen/should_run/T6084.stdout
@@ -0,0 +1,3 @@
+Hello World!
+Hello World!
+Hello World!
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index f7b36ff..768d320 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -115,3 +115,4 @@ test('T7600', normal, compile_and_run, [''])
 test('T8103', only_ways(['normal']), compile_and_run, [''])
 test('T7953', reqlib('random'), compile_and_run, [''])
 test('T8256',normal, compile_and_run, [''])
+test('T6084',normal, compile_and_run, ['-O2'])



More information about the ghc-commits mailing list