Repository : ssh://darcs.haskell.org//srv/darcs/packages/containers

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ea4a6e42248dc26853ece3f29a9c25bccfe810d1

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

commit ea4a6e42248dc26853ece3f29a9c25bccfe810d1
Author: Johan Tibell <[email protected]>
Date:   Mon Nov 21 16:44:32 2011 -0800

    Remove two remaining bang patterns

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

 Data/Map/Strict.hs |    8 ++++----
 1 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs
index 2c1c218..71a6620 100644
--- a/Data/Map/Strict.hs
+++ b/Data/Map/Strict.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, NoBangPatterns #-}
+{-# LANGUAGE CPP #-}
 #if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Safe #-}
 #endif
@@ -391,8 +391,8 @@ insertWithKey = go
         case compare kx ky of
             LT -> balanceL ky y (go f kx x l) r
             GT -> balanceR ky y l (go f kx x r)
-            EQ -> let !x' = f kx x y
-                  in Bin sy kx x' l r
+            EQ -> let x' = f kx x y
+                  in x' `seq` Bin sy kx x' l r
 #if __GLASGOW_HASKELL__ >= 700
 {-# INLINEABLE insertWithKey #-}
 #else
@@ -823,7 +823,7 @@ intersectionWithKey f t1@(Bin s1 k1 x1 l1 r1) t2@(Bin s2 k2 
x2 l2 r2) =
             tl            = intersectionWithKey f l1 lt
             tr            = intersectionWithKey f r1 gt
       in case found of
-      Just x -> let !x' = f k1 x1 x in join k1 x' tl tr
+      Just x -> let x' = f k1 x1 x in x' `seq` join k1 x' tl tr
       Nothing -> merge tl tr
 #if __GLASGOW_HASKELL__ >= 700
 {-# INLINABLE intersectionWithKey #-}



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

Reply via email to