Proposal: Non-allocating way to iterate over a Data.Map: traverseWithKey_

Shachaf Ben-Kiki shachaf at gmail.com
Tue Jul 2 22:17:55 CEST 2013


On Tue, Jul 2, 2013 at 12:32 PM, Ryan Newton <rrnewton at gmail.com> wrote:
> On Tue, Jul 2, 2013 at 10:29 AM, Shachaf Ben-Kiki <shachaf at gmail.com> wrote:
>> Is there a reason you couldn't implement this just as well using
>> traverseWithKey, à la
>>
>> http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/Control-Lens-Fold.html#v:traverseOf_
>
> That function looks more overloaded than the traverse in Data.Map that I'm
> referring to, e.g. here:
>
> http://www.haskell.org/ghc/docs/latest/html/libraries/containers/Data-Map-Strict.html#g:13
>
> I'm afraid I don't understand the proposal then -- is it to use lens
> somehow?  For the traversal I need to do over a Data.Map.Map, I need to fix
> 't' to be IO or Par or whatever I'm working with, so that the (k -> a -> t
> b) function I'm passing in can do the effects I need.
>
> To be specific I'm proposing providing these variants:
>
>    traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map
> k b)
>    traverseWithKey_ :: Applicative t => (k -> a -> t ()) -> Map k a -> t ()
>
> And without exposing the latter natively, I still don't understand how to
> trick the former into not allocating, if that's the proposal.
>
>    -Ryan
>

The suggestion is that

(a) You can derive a balanced foldMapWithKey from traverseWithKey, as follows:

    foldMapWithKey :: Monoid r => (k -> a -> r) -> M.Map k a -> r
    foldMapWithKey f = getConst . M.traverseWithKey (\k x -> Const (f k x))

Since the Applicative used is Const (newtype Const m a = Const m), the
structure is never built up.

(b) You can derive traverseWithKey_ from foldMapWithKey, e.g. as follows:

    newtype Traverse_ f = Traverse_ { runTraverse_ :: f () }

    instance Applicative f => Monoid (Traverse_ f) where
      mempty = Traverse_ (pure ())
      Traverse_ a `mappend` Traverse_ b = Traverse_ (a *> b)

    traverseWithKey_ :: Applicative f => (k -> a -> f ()) -> M.Map k a -> f ()
    traverseWithKey_ f = runTraverse_ . foldMapWithKey (\k x ->
Traverse_ (void (f k x)))

As Henning and Edward pointed out, though, foldrWithKey/foldlWithKey
are already exported by Data.Map (and they give you right/left
associativity, so they're possibly better... Of course, you can derive
them from traverseWithKey too!).

    Shachaf



More information about the Libraries mailing list