Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/110d2c197bda03ab6ecff4769e311b61221afa8e

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

commit 110d2c197bda03ab6ecff4769e311b61221afa8e
Author: Simon Marlow <[email protected]>
Date:   Wed May 25 14:56:30 2011 +0100

    fix test following changes to inlining heuristics

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

 .../ghc-regress/simplCore/should_compile/T4306.hs  |    6 ++++--
 1 files changed, 4 insertions(+), 2 deletions(-)

diff --git a/tests/ghc-regress/simplCore/should_compile/T4306.hs 
b/tests/ghc-regress/simplCore/should_compile/T4306.hs
index 7675986..ba32981 100644
--- a/tests/ghc-regress/simplCore/should_compile/T4306.hs
+++ b/tests/ghc-regress/simplCore/should_compile/T4306.hs
@@ -6,5 +6,7 @@ module T4306 where
 data D = D {-# UNPACK #-} !Double {-# UNPACK #-} !Double  
 data UPD = UPD {-# UNPACK #-} !Double D
 
-upd (UPD _ (D x _)) = sqrt $! (x*x + x*x + sin x)
-
+upd (UPD _ (D x _)) = sqrt $! (x*x + x*x + sin x + x*x + x*x + cos x + x*x + 
x*x + tan x +
+                               x*x + x*x + sin x + x*x + x*x + cos x + x*x + 
x*x + tan x +
+                               x*x + x*x + sin x + x*x + x*x + cos x + x*x + 
x*x + tan x)
+                               -- make the rhs large enough to be 
worker/wrapperred



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to