[commit: ghc] wip/nested-cpr: CPR testcase: AnonLambda (b4c2be0)

git at git.haskell.org git at git.haskell.org
Tue Feb 4 18:27:39 UTC 2014


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

On branch  : wip/nested-cpr
Link       : http://ghc.haskell.org/trac/ghc/changeset/b4c2be09d2a4f7f9d6b6008e450ffd0d29b6fdea/ghc

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

commit b4c2be09d2a4f7f9d6b6008e450ffd0d29b6fdea
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Jan 21 12:18:08 2014 +0000

    CPR testcase: AnonLambda


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

b4c2be09d2a4f7f9d6b6008e450ffd0d29b6fdea
 testsuite/tests/stranal/sigs/AnonLambda.hs                  |   11 +++++++++++
 .../stranal/sigs/{InfiniteCPR.stderr => AnonLambda.stderr}  |    3 ++-
 testsuite/tests/stranal/sigs/all.T                          |    1 +
 3 files changed, 14 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/stranal/sigs/AnonLambda.hs b/testsuite/tests/stranal/sigs/AnonLambda.hs
new file mode 100644
index 0000000..f79b940
--- /dev/null
+++ b/testsuite/tests/stranal/sigs/AnonLambda.hs
@@ -0,0 +1,11 @@
+module AnonLambda where
+
+g :: Int -> Bool
+{-# NOINLINE g #-}
+g = (==0)
+
+-- This test ensures that the CPR property of the anonymous lambda
+-- Does not escape to f (which has arity 1)
+
+f = \x -> if g x then \y -> x + y + 1
+                 else \y -> x + y + 2
diff --git a/testsuite/tests/stranal/sigs/InfiniteCPR.stderr b/testsuite/tests/stranal/sigs/AnonLambda.stderr
similarity index 54%
copy from testsuite/tests/stranal/sigs/InfiniteCPR.stderr
copy to testsuite/tests/stranal/sigs/AnonLambda.stderr
index 70a3cdf..350b61c 100644
--- a/testsuite/tests/stranal/sigs/InfiniteCPR.stderr
+++ b/testsuite/tests/stranal/sigs/AnonLambda.stderr
@@ -1,5 +1,6 @@
 
 ==================== Strictness signatures ====================
-InfiniteCPR.f: <L,U>m(,m(tm(,),tm(,)))
+AnonLambda.f: <S(S),U(U)>
+AnonLambda.g: <S(S),1*U(1*U)>
 
 
diff --git a/testsuite/tests/stranal/sigs/all.T b/testsuite/tests/stranal/sigs/all.T
index 448dc8e..7cc7618 100644
--- a/testsuite/tests/stranal/sigs/all.T
+++ b/testsuite/tests/stranal/sigs/all.T
@@ -19,3 +19,4 @@ test('CaseBinderCPR', normal, compile, [''])
 test('InfiniteCPR', normal, compile, [''])
 test('InfiniteCPRDepth0', normal, compile, [''])
 test('InfiniteCPRDepth1', normal, compile, [''])
+test('AnonLambda', normal, compile, [''])



More information about the ghc-commits mailing list