On Wed, Aug 11, 2010 at 6:18 PM, Johan Tibell <johan.tibell@gmail.com> wrote:
We're also missing a bunch of strict versions of traversals functions, like folds. I needed a strict fold the other day and found that there isn't one. Should we just go ahead and add a strict version for all the functions where that makes sense?

I've created a proposal to add a strict left fold, see separate email. In the process of doing so I've discovered that the whole foo/fooWithKey duplication is unnecessary, at least from a performance perspective. Assuming that you define your folds like so:

    -- | /O(n)/. Strict version of 'foldlWithKey'.
    foldlWithKey' :: (b -> k -> a -> b) -> b -> Map k a -> b
    foldlWithKey' f z0 m = go z0 m
      where
        go z _ | z `seq` False = undefined
        go z Tip               = z
        go z (Bin _ kx x l r)  = go (f (go z l) kx x) r
    {-# INLINE foldlWithKey' #-}

the expression

    M.foldlWithKey' (\n _ v -> n + v) 0 m

will be optimized to code that doesn't touch the key field in the `Bin` constructor, just as if you wrote a foldl' function that doesn't pass the key to the combination function.

It's probably not feasible to remove the duplication from e.g. the Data.Map API, but it's worth keeping in mind when designing data structure APIs in the future.

Cheers,
Johan