[commit: ghc] wip/oneShot: Inline foldl' (6949f86)
git at git.haskell.org
git at git.haskell.org
Sat Oct 25 14:07:41 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/oneShot
Link : http://ghc.haskell.org/trac/ghc/changeset/6949f86a9401156999230c7d016fbcd4ce1c69b4/ghc
>---------------------------------------------------------------
commit 6949f86a9401156999230c7d016fbcd4ce1c69b4
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Sat Oct 25 16:07:35 2014 +0200
Inline foldl'
(otherwise the oneShot gets lost in the unfolding in the interface)
>---------------------------------------------------------------
6949f86a9401156999230c7d016fbcd4ce1c69b4
libraries/base/Data/OldList.hs | 1 +
1 file changed, 1 insertion(+)
diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index 75fba35..b207b5e 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -1059,6 +1059,7 @@ unfoldr f b0 = build (\c n ->
-- | A strict version of 'foldl'.
foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b
+{-# INLINE foldl' #-}
foldl' k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> z `seq` fn (k z v))) (id :: b -> b) xs z0
-- Implementing foldl' via foldr is only a good idea if the compiler can optimize
-- the resulting code (eta-expand the recursive "go"), so this needs -fcall-arity!
More information about the ghc-commits
mailing list