[commit: testsuite] master: Test Trac #8377 (b499ed1)
git at git.haskell.org
git at git.haskell.org
Mon Sep 30 00:23:57 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/b499ed1ea71f58c02d5b71e147b938ca0b96f8a1/testsuite
>---------------------------------------------------------------
commit b499ed1ea71f58c02d5b71e147b938ca0b96f8a1
Author: Takano Akio <aljee at hyper.cx>
Date: Sat Sep 28 20:05:33 2013 +0900
Test Trac #8377
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
b499ed1ea71f58c02d5b71e147b938ca0b96f8a1
tests/ghci/should_run/T8377.hs | 14 ++++++++++++++
tests/ghci/should_run/T8377.stdout | 1 +
tests/ghci/should_run/all.T | 1 +
3 files changed, 16 insertions(+)
diff --git a/tests/ghci/should_run/T8377.hs b/tests/ghci/should_run/T8377.hs
new file mode 100644
index 0000000..4b6e576
--- /dev/null
+++ b/tests/ghci/should_run/T8377.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE MagicHash #-}
+import System.Mem
+import GHC.Base
+
+main = do
+ let list = concatMap buildThunk [0..10000]
+ length list `seq` performGC
+ print $ last list
+
+buildThunk :: Int -> [Int]
+buildThunk (I# k) = [f k]
+
+f :: Int# -> Int
+f x = I# x
diff --git a/tests/ghci/should_run/T8377.stdout b/tests/ghci/should_run/T8377.stdout
new file mode 100644
index 0000000..5caff40
--- /dev/null
+++ b/tests/ghci/should_run/T8377.stdout
@@ -0,0 +1 @@
+10000
diff --git a/tests/ghci/should_run/all.T b/tests/ghci/should_run/all.T
index f4d06a6..c42681f 100644
--- a/tests/ghci/should_run/all.T
+++ b/tests/ghci/should_run/all.T
@@ -19,3 +19,4 @@ test('T3171',
['$MAKE -s --no-print-directory T3171'])
test('ghcirun004', just_ghci, compile_and_run, [''])
+test('T8377', just_ghci, compile_and_run, [''])
More information about the ghc-commits
mailing list