[commit: ghc] master: Add a test case for #5949 (19e09df)

git at git.haskell.org git at git.haskell.org
Fri Jan 17 15:12:03 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/19e09df47f48707718150fb9b4b9135ec742bed2/ghc

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

commit 19e09df47f48707718150fb9b4b9135ec742bed2
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri Jan 17 14:08:30 2014 +0000

    Add a test case for #5949


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

19e09df47f48707718150fb9b4b9135ec742bed2
 testsuite/tests/perf/should_run/T5949.hs |   56 ++++++++++++++++++++++++++++++
 testsuite/tests/perf/should_run/all.T    |    8 +++++
 2 files changed, 64 insertions(+)

diff --git a/testsuite/tests/perf/should_run/T5949.hs b/testsuite/tests/perf/should_run/T5949.hs
new file mode 100644
index 0000000..0fcfb63
--- /dev/null
+++ b/testsuite/tests/perf/should_run/T5949.hs
@@ -0,0 +1,56 @@
+import Data.List
+
+{-
+This should get a worker that takes three arguments.
+
+bad:
+
+Rec {
+$we_r1z8
+  :: (GHC.Types.Int, GHC.Types.Int)
+     -> GHC.Prim.Int# -> (# GHC.Types.Int, GHC.Types.Int #)
+[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType S(AA)L]
+$we_r1z8 =
+  \ (w_s1yf :: (GHC.Types.Int, GHC.Types.Int))
+    (ww_s1yi :: GHC.Prim.Int#) ->
+    case GHC.Prim.># ww_s1yi 10 of _ {
+      GHC.Types.False -> $we_r1z8 w_s1yf (GHC.Prim.+# ww_s1yi 1);
+      GHC.Types.True ->
+        case w_s1yf of _ { (ww2_s1yp, ww3_s1yq) ->
+        (# ww2_s1yp, ww3_s1yq #)
+        }
+    }
+end Rec }
+
+Good:
+
+Rec {
+$we_r2qK
+  :: GHC.Types.Int
+     -> GHC.Types.Int
+     -> GHC.Prim.Int#
+     -> (# GHC.Types.Int, GHC.Types.Int #)
+[GblId, Arity=3, Caf=NoCafRefs, Str=DmdType <L,U><L,U><L,U>]
+$we_r2qK =
+  \ (ww_s2pS :: GHC.Types.Int)
+    (ww1_s2pT :: GHC.Types.Int)
+    (ww2_s2pX :: GHC.Prim.Int#) ->
+    case GHC.Prim.tagToEnum# @ GHC.Types.Bool (GHC.Prim.># ww2_s2pX 10)
+    of _ [Occ=Dead] {
+      GHC.Types.False ->
+        $we_r2qK ww_s2pS ww1_s2pT (GHC.Prim.+# ww2_s2pX 1);
+      GHC.Types.True -> (# ww_s2pS, ww1_s2pT #)
+    }
+end Rec }
+
+-}
+
+
+
+e :: (Int, Int) -> Int -> (Int, Int)
+e x y = x `seq` if y > 10
+        then x
+        else e x (y + 1)
+
+
+main = foldr (seq) 0 [e (n,0) 0| n <- [0..10000]] `seq` return ()
diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T
index 8966310..99b8aab 100644
--- a/testsuite/tests/perf/should_run/all.T
+++ b/testsuite/tests/perf/should_run/all.T
@@ -298,3 +298,11 @@ test('T7850',
      compile_and_run,
      ['-O'])
 
+test('T5949',
+     [stats_num_field('bytes allocated',
+                      [ (wordsize(64), 201008, 10)]),
+                      # previously, it was >400000 bytes
+      only_ways(['normal'])],
+     compile_and_run,
+     ['-O'])
+



More information about the ghc-commits mailing list