Proposal: Add a strict version of foldlWithKey to Data.Map

Hi, The current API doesn't offer any efficient way to do something simple as e.g. summing the values in a map. I suggest we add a foldlWithKey' function: http://hackage.haskell.org/trac/ghc/ticket/4261 Discussion deadline: 2 weeks Cheers, Johan

On Wed, Aug 18, 2010 at 02:00:39PM +0200, Johan Tibell wrote:
The current API doesn't offer any efficient way to do something simple as e.g. summing the values in a map. I suggest we add a foldlWithKey' function:
Shouldn't (go z l) be forced too? Thanks Ian

On Sat, Aug 21, 2010 at 1:45 PM, Ian Lynagh
On Wed, Aug 18, 2010 at 02:00:39PM +0200, Johan Tibell wrote:
The current API doesn't offer any efficient way to do something simple as e.g. summing the values in a map. I suggest we add a foldlWithKey'
function:
Shouldn't (go z l) be forced too?
It makes sense to me to do so but the core looks worse for some reason: foldlWithKey' :: (b -> k -> a -> b) -> b -> Map k a -> b foldlWithKey' f z0 m0 = go z0 m0 where go z _ | z `seq` False = undefined go z Tip = z go z (Bin _ kx x l r) = let z' = go z l z'' = f z' kx x in z' `seq` z'' `seq` go z'' r {-# INLINE foldlWithKey' #-} with the test module Test (test) where import qualified Data.Map as M test :: M.Map Int Int -> Int test m = M.foldlWithKey' (\n k v -> n + k + v) 0 m we get the core go :: Int -> Data.Map.Map Int Int -> Int go = \ (z :: Int) (ds_al9 :: Data.Map.Map Int Int) -> case ds_al9 of _ { Data.Map.Tip -> z; Data.Map.Bin _ kx x l r -> case go z l of _ { I# ipv_slJ -> case kx of _ { I# kx# -> case x of _ { I# x# -> go (I# (+# (+# ipv_slJ kx#) x#)) r } } } } which doesn't have an unboxed accumulator. I'm not sure why. Any ideas? Cheers, Johan

On Sun, Aug 22, 2010 at 9:45 AM, Johan Tibell
On Sat, Aug 21, 2010 at 1:45 PM, Ian Lynagh
wrote: On Wed, Aug 18, 2010 at 02:00:39PM +0200, Johan Tibell wrote:
The current API doesn't offer any efficient way to do something simple
as
e.g. summing the values in a map. I suggest we add a foldlWithKey' function:
Shouldn't (go z l) be forced too?
It makes sense to me to do so but the core looks worse for some reason:
foldlWithKey' :: (b -> k -> a -> b) -> b -> Map k a -> b foldlWithKey' f z0 m0 = go z0 m0 where go z _ | z `seq` False = undefined go z Tip = z go z (Bin _ kx x l r) = let z' = go z l z'' = f z' kx x
By the way, the problem remains if the unnecessary forcing of z'' is removed or the guard that forces z is removed.
in z' `seq` z'' `seq` go z'' r {-# INLINE foldlWithKey' #-}

On Sun, Aug 22, 2010 at 09:45:32AM +0200, Johan Tibell wrote:
On Sat, Aug 21, 2010 at 1:45 PM, Ian Lynagh
wrote: On Wed, Aug 18, 2010 at 02:00:39PM +0200, Johan Tibell wrote:
The current API doesn't offer any efficient way to do something simple as e.g. summing the values in a map. I suggest we add a foldlWithKey'
function:
Shouldn't (go z l) be forced too?
It makes sense to me to do so but the core looks worse for some reason:
Well, if there's a GHC code performance bug then we should fix it, but I don't think we should use a workaround in the libraries that gives a function the wrong strictness.
which doesn't have an unboxed accumulator. I'm not sure why.
Can you file a GHC ticket with a standalone testcase please? Thanks Ian

On Sun, Aug 22, 2010 at 2:47 PM, Ian Lynagh
Well, if there's a GHC code performance bug then we should fix it, but I don't think we should use a workaround in the libraries that gives a function the wrong strictness.
The generated core has the strictness we want, the Haskell just doesn't reflect that (which means it could break in the future). I think we should stick with the current definition until we can come up with a better one that still gives the right core. I've filed a bug: http://hackage.haskell.org/trac/ghc/ticket/4267

On Mon, Aug 23, 2010 at 12:23:52AM +0200, Johan Tibell wrote:
On Sun, Aug 22, 2010 at 2:47 PM, Ian Lynagh
wrote: Well, if there's a GHC code performance bug then we should fix it, but I don't think we should use a workaround in the libraries that gives a function the wrong strictness.
The generated core has the strictness we want
In your example, yes, but if f ignores its first argument then it doesn't. Thanks Ian

On Mon, Aug 23, 2010 at 12:33 AM, Ian Lynagh
On Mon, Aug 23, 2010 at 12:23:52AM +0200, Johan Tibell wrote:
On Sun, Aug 22, 2010 at 2:47 PM, Ian Lynagh
wrote: Well, if there's a GHC code performance bug then we should fix it, but I don't think we should use a workaround in the libraries that gives a function the wrong strictness.
The generated core has the strictness we want
In your example, yes, but if f ignores its first argument then it doesn't.
That's a good point. Do you have an alternate definition in mind that would work better? -- Johan
participants (2)
-
Ian Lynagh
-
Johan Tibell