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

Johan Tibell johan.tibell at gmail.com
Sun Aug 22 03:45:32 EDT 2010


On Sat, Aug 21, 2010 at 1:45 PM, Ian Lynagh <igloo at earth.li> 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:
> >
> >     http://hackage.haskell.org/trac/ghc/ticket/4261
>
> 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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/libraries/attachments/20100822/d34ae47c/attachment.html


More information about the Libraries mailing list