[commit: ghc] wip/nested-cpr: CPR test case: Case binder CPR (3336339)
git at git.haskell.org
git at git.haskell.org
Tue Feb 4 18:27:13 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nested-cpr
Link : http://ghc.haskell.org/trac/ghc/changeset/3336339b03e5961a3064c43a8ab062f080b6ef55/ghc
>---------------------------------------------------------------
commit 3336339b03e5961a3064c43a8ab062f080b6ef55
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Tue Jan 14 09:36:34 2014 +0000
CPR test case: Case binder CPR
>---------------------------------------------------------------
3336339b03e5961a3064c43a8ab062f080b6ef55
testsuite/tests/stranal/sigs/CaseBinderCPR.hs | 15 +++++++++++++++
.../stranal/sigs/{T8569.stderr => CaseBinderCPR.stderr} | 2 +-
testsuite/tests/stranal/sigs/all.T | 1 +
3 files changed, 17 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/stranal/sigs/CaseBinderCPR.hs b/testsuite/tests/stranal/sigs/CaseBinderCPR.hs
new file mode 100644
index 0000000..13f2163
--- /dev/null
+++ b/testsuite/tests/stranal/sigs/CaseBinderCPR.hs
@@ -0,0 +1,15 @@
+module CaseBinderCPR where
+
+-- This example, taken from nofib's transform (and heavily reduced) ensures that
+-- CPR information is added to a case binder
+
+f_list_cmp::(t1 -> t1 -> Int) -> [t1] -> [t1] -> Int;
+f_list_cmp a_cmp [] []= 0
+f_list_cmp a_cmp [] a_ys= -1
+f_list_cmp a_cmp a_xs []= 1
+f_list_cmp a_cmp (a_x:a_xs) (a_y:a_ys)=
+ if r_order == 0
+ then f_list_cmp a_cmp a_xs a_ys
+ else r_order
+ where
+ r_order = a_cmp a_x a_y
diff --git a/testsuite/tests/stranal/sigs/T8569.stderr b/testsuite/tests/stranal/sigs/CaseBinderCPR.stderr
similarity index 53%
copy from testsuite/tests/stranal/sigs/T8569.stderr
copy to testsuite/tests/stranal/sigs/CaseBinderCPR.stderr
index d33935e..f2ea61d 100644
--- a/testsuite/tests/stranal/sigs/T8569.stderr
+++ b/testsuite/tests/stranal/sigs/CaseBinderCPR.stderr
@@ -1,5 +1,5 @@
==================== Strictness signatures ====================
-T8569.addUp: <S,1*U><L,U>
+CaseBinderCPR.f_list_cmp: <L,C(C1(U(U)))><S,1*U><S,1*U>m()
diff --git a/testsuite/tests/stranal/sigs/all.T b/testsuite/tests/stranal/sigs/all.T
index 9d36479..81a8d4b 100644
--- a/testsuite/tests/stranal/sigs/all.T
+++ b/testsuite/tests/stranal/sigs/all.T
@@ -15,3 +15,4 @@ test('FacState', expect_broken(1600), compile, [''])
test('UnsatFun', normal, compile, [''])
test('BottomFromInnerLambda', normal, compile, [''])
test('DmdAnalGADTs', normal, compile, [''])
+test('CaseBinderCPR', normal, compile, [''])
More information about the ghc-commits
mailing list