[commit: ghc] wip/oneShot: Use oneShot in the definition of foldl etc. (6f101d2)
Simon Peyton Jones
simonpj at microsoft.com
Sun Oct 26 21:03:10 UTC 2014
No Notes! Surely, surely it deserves one!
Simon
| -----Original Message-----
| From: ghc-commits [mailto:ghc-commits-bounces at haskell.org] On Behalf Of
| git at git.haskell.org
| Sent: 25 October 2014 11:27
| To: ghc-commits at haskell.org
| Subject: [commit: ghc] wip/oneShot: Use oneShot in the definition of
| foldl etc. (6f101d2)
|
| Repository : ssh://git@git.haskell.org/ghc
|
| On branch : wip/oneShot
| Link :
| http://ghc.haskell.org/trac/ghc/changeset/6f101d20805fb52de0423bc8beab373
| b94bd4a7d/ghc
|
| >---------------------------------------------------------------
|
| commit 6f101d20805fb52de0423bc8beab373b94bd4a7d
| Author: Joachim Breitner <mail at joachim-breitner.de>
| Date: Sat Oct 25 12:27:06 2014 +0200
|
| Use oneShot in the definition of foldl etc.
|
|
| >---------------------------------------------------------------
|
| 6f101d20805fb52de0423bc8beab373b94bd4a7d
| libraries/base/Data/OldList.hs | 5 +++--
| libraries/base/GHC/List.lhs | 6 +++---
| 2 files changed, 6 insertions(+), 5 deletions(-)
|
| diff --git a/libraries/base/Data/OldList.hs
| b/libraries/base/Data/OldList.hs
| index 0e6709e..75fba35 100644
| --- a/libraries/base/Data/OldList.hs
| +++ b/libraries/base/Data/OldList.hs
| @@ -499,7 +499,8 @@ pairWithNil x = (x, [])
|
| mapAccumLF :: (acc -> x -> (acc, y)) -> x -> (acc -> (acc, [y])) -> acc
| -> (acc, [y])
| {-# INLINE [0] mapAccumLF #-}
| -mapAccumLF f = \x r s -> let (s', y) = f s x
| +mapAccumLF f = \x r -> oneShot $ \s ->
| + let (s', y) = f s x
| (s'', ys) = r s'
| in (s'', y:ys)
|
| @@ -1058,7 +1059,7 @@ unfoldr f b0 = build (\c n ->
|
| -- | A strict version of 'foldl'.
| foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b
| -foldl' k z0 xs = foldr (\(v::a) (fn::b->b) (z::b) -> z `seq` fn (k z v))
| (id :: b -> b) xs z0
| +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!
| -- Also see #7994
| diff --git a/libraries/base/GHC/List.lhs b/libraries/base/GHC/List.lhs
| index 2d01678..c7a0cb3 100644
| --- a/libraries/base/GHC/List.lhs
| +++ b/libraries/base/GHC/List.lhs
| @@ -186,7 +186,7 @@ filterFB c p x r | p x = x `c` r
|
| foldl :: forall a b. (b -> a -> b) -> b -> [a] -> b
| {-# INLINE foldl #-}
| -foldl k z0 xs = foldr (\(v::a) (fn::b->b) (z::b) -> fn (k z v)) (id :: b
| -> b) xs z0
| +foldl k z0 xs = foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> 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!
| -- Also see #7994
| @@ -221,7 +221,7 @@ scanl = scanlGo
|
| {-# INLINE [0] scanlFB #-}
| scanlFB :: (b -> a -> b) -> (b -> c -> c) -> a -> (b -> c) -> b -> c
| -scanlFB f c = \b g x -> let b' = f x b in b' `c` g b'
| +scanlFB f c = \b g -> oneShot (\x -> let b' = f x b in b' `c` g b')
|
| {-# INLINE [0] constScanl #-}
| constScanl :: a -> b -> a
| @@ -258,7 +258,7 @@ scanl' = scanlGo'
|
| {-# INLINE [0] scanlFB' #-}
| scanlFB' :: (b -> a -> b) -> (b -> c -> c) -> a -> (b -> c) -> b -> c
| -scanlFB' f c = \b g x -> let b' = f x b in b' `seq` b' `c` g b'
| +scanlFB' f c = \b g -> oneShot (\x -> let b' = f x b in b' `seq` b' `c`
| g b')
|
| {-# INLINE [0] flipSeqScanl' #-}
| flipSeqScanl' :: a -> b -> a
|
| _______________________________________________
| ghc-commits mailing list
| ghc-commits at haskell.org
| http://www.haskell.org/mailman/listinfo/ghc-commits
More information about the ghc-devs
mailing list