[commit: testsuite] master: Add nested CPR testcase (9f4c591)
git at git.haskell.org
git at git.haskell.org
Mon Dec 9 18:44:44 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/9f4c591f6b82bf6f06e844fa60df8289303e6068/testsuite
>---------------------------------------------------------------
commit 9f4c591f6b82bf6f06e844fa60df8289303e6068
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Dec 9 16:35:28 2013 +0000
Add nested CPR testcase
>---------------------------------------------------------------
9f4c591f6b82bf6f06e844fa60df8289303e6068
tests/stranal/sigs/FacState.hs | 6 ++++++
tests/stranal/sigs/{StrAnalExample.stderr => FacState.stderr} | 2 +-
tests/stranal/sigs/all.T | 2 +-
3 files changed, 8 insertions(+), 2 deletions(-)
diff --git a/tests/stranal/sigs/FacState.hs b/tests/stranal/sigs/FacState.hs
new file mode 100644
index 0000000..470bbd9
--- /dev/null
+++ b/tests/stranal/sigs/FacState.hs
@@ -0,0 +1,6 @@
+module FacState where
+
+
+fac :: Int -> a -> (a, Int)
+fac n s | n < 2 = (s,1)
+ | otherwise = case fac (n-1) s of (s',n') -> let n'' = n*n' in n'' `seq` (s',n'')
diff --git a/tests/stranal/sigs/StrAnalExample.stderr b/tests/stranal/sigs/FacState.stderr
similarity index 60%
copy from tests/stranal/sigs/StrAnalExample.stderr
copy to tests/stranal/sigs/FacState.stderr
index dbe4770..133ad6e 100644
--- a/tests/stranal/sigs/StrAnalExample.stderr
+++ b/tests/stranal/sigs/FacState.stderr
@@ -1,5 +1,5 @@
==================== Strictness signatures ====================
-StrAnalExample.foo: <S,1*U>
+FacState.fac: <S,1*U(U)><L,U>dm1(d,tm1(d))
diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T
index d77cd9e..ca47b52 100644
--- a/tests/stranal/sigs/all.T
+++ b/tests/stranal/sigs/all.T
@@ -11,4 +11,4 @@ test('StrAnalExample', normal, compile, [''])
test('T8569', expect_broken(8569), compile, [''])
test('HyperStrUse', normal, compile, [''])
test('T8598', normal, compile, [''])
-
+test('FacState', expect_broken(1600), compile, [''])
More information about the ghc-commits
mailing list