[commit: packages/bytestring] master: Replace explicit uses of seq with bang patterns (cf29654)

git at git.haskell.org git at git.haskell.org
Fri Jan 23 22:43:29 UTC 2015


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

On branch  : master
Link       : http://git.haskell.org/packages/bytestring.git/commitdiff/cf29654289198dc652f306b56812e2e4f22ed9ed

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

commit cf29654289198dc652f306b56812e2e4f22ed9ed
Author: Duncan Coutts <duncan at community.haskell.org>
Date:   Sun Dec 14 13:15:45 2014 +0000

    Replace explicit uses of seq with bang patterns


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

cf29654289198dc652f306b56812e2e4f22ed9ed
 Data/ByteString.hs      |  6 ++----
 Data/ByteString/Lazy.hs | 15 +++++++--------
 2 files changed, 9 insertions(+), 12 deletions(-)

diff --git a/Data/ByteString.hs b/Data/ByteString.hs
index b839150..afe1442 100644
--- a/Data/ByteString.hs
+++ b/Data/ByteString.hs
@@ -1697,8 +1697,7 @@ hGetLine h =
          else haveBuf h_ buf 0 []
  where
 
-  fill h_ at Handle__{haByteBuffer,haDevice} buf len xss =
-    len `seq` do
+  fill h_ at Handle__{haByteBuffer,haDevice} buf !len xss = do
     (r,buf') <- Buffered.fillReadBuffer haDevice buf
     if r == 0
        then do writeIORef haByteBuffer buf{ bufR=0, bufL=0 }
@@ -1757,8 +1756,7 @@ hGetLine h = wantReadableHandle "Data.ByteString.hGetLine" h $ \ handle_ -> do
         hGetLineBufferedLoop handle_ ref buf 0 []
 
     hGetLineBufferedLoop handle_ ref
-            buf at Buffer{ bufRPtr=r, bufWPtr=w, bufBuf=raw } len xss =
-        len `seq` do
+            buf at Buffer{ bufRPtr=r, bufWPtr=w, bufBuf=raw } !len xss = do
         off <- findEOL r w raw
         let new_len = len + off - r
         xs <- mkPS raw r off
diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs
index 2bb109d..26b5965 100644
--- a/Data/ByteString/Lazy.hs
+++ b/Data/ByteString/Lazy.hs
@@ -479,9 +479,8 @@ foldl f z = go z
 -- | 'foldl\'' is like 'foldl', but strict in the accumulator.
 foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a
 foldl' f z = go z
-  where go a _ | a `seq` False = undefined
-        go a Empty        = a
-        go a (Chunk c cs) = go (S.foldl' f a c) cs
+  where go !a Empty        = a
+        go !a (Chunk c cs) = go (S.foldl' f a c) cs
 {-# INLINE foldl' #-}
 
 -- | 'foldr', applied to a binary operator, a starting value
@@ -610,7 +609,7 @@ scanl f z = snd . foldl k (z,singleton z)
 -- > iterate f x == [x, f x, f (f x), ...]
 --
 iterate :: (Word8 -> Word8) -> Word8 -> ByteString
-iterate f = unfoldr (\x -> case f x of x' -> x' `seq` Just (x', x'))
+iterate f = unfoldr (\x -> case f x of !x' -> Just (x', x'))
 
 -- | @'repeat' x@ is an infinite ByteString, with @x@ the value of every
 -- element.
@@ -918,10 +917,10 @@ elemIndexEnd :: Word8 -> ByteString -> Maybe Int64
 elemIndexEnd w = elemIndexEnd' 0
   where
     elemIndexEnd' _ Empty = Nothing
-    elemIndexEnd' n (Chunk c cs) = let
-      n' = n + S.length c
-      i = fmap (fromIntegral . (n +)) $ S.elemIndexEnd w c
-      in n' `seq` i `seq` elemIndexEnd' n' cs `mplus` i
+    elemIndexEnd' n (Chunk c cs) =
+      let !n' = n + S.length c
+          !i  = fmap (fromIntegral . (n +)) $ S.elemIndexEnd w c
+      in elemIndexEnd' n' cs `mplus` i
 
 -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning
 -- the indices of all elements equal to the query element, in ascending order.



More information about the ghc-commits mailing list