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

Milan Straka fox at ucw.cz
Tue Aug 6 22:19:41 CEST 2013


Hi Edward,

> -----Original message-----
> From: Edward Kmett <ekmett at gmail.com>
> Sent: 6 Aug 2013, 14:26
>
> On Tue, Aug 6, 2013 at 2:09 PM, Milan Straka <fox at ucw.cz> wrote:
> 
> > Hi Edward,I am not suggesting we should change the behaviour of existing
> > functions
> > and traverseWithKey_ should definitely use the same order as
> > traverseWithKey. Changing semantics without changing type signatures is
> > really suspicious and usually plainly wrong.
> >
> 
> I wholeheartedly agree. =) I was just basing that on the code Ryan posted:
> 
> >   traverseWithKey_ f = go
> >     where go Tip = pure ()
> >           go (Bin _ k v l r) = f k v *> go l *> go r
> >
> >
> ... which visits the key/value pairs out of order unlike, say:
> 
>   go (Bin _ k v l r = go l *> f k v *> go r

Oh, yes, we will definitely use the definition you suggest.

> > Nevertheless, I was wondering whether we should have a monadic fold
> > (foldrM and foldlM) which would process the elements in a given order
> > (ascending and descending, analogously to foldr and foldl). From one
> > point of view, we can implement foldrM and foldlM using foldr and foldl,
> >
> 
> Sure, foldrM is typically implemented in terms of foldl and foldlM is
> typically implemented in terms of foldr.
> 
> Do the usual definitions like that leak on a Map?

It is difficult to say whether it is a 'leak'. These methods (they are
the same as Foldable.foldrM and Foldable.foldlM) heap-allocate space
linear in the size of the map (to create the closures). When implemented
directly, they do not heap-allocate.

> foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m
> bfoldrM f z0 xs = foldl f' return xs z0  where f' k x z = f x z >>= k
> 
> foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m
> afoldlM f z0 xs = foldr f' return xs z0  where f' x k z = f z x >>= k
> 
> nevertheless using linear heap space complexity compared to constant
> > heap space complexity we can achieve with specialized implementations.
> > This is the same situation as traverseWithKey_ -- we can implement it
> > using traverseWithKey, but the heap space complexity increases.
> >
> 
> traverseWithKey_ would normally be implemented with an appropriate newtype
> and foldMapWithKey, rather than traverseWithKey. Does that also leak?

That does not leak, as Shachaf Ben-Kiki pointed out. That is one of the
reasons why this discussion is so long :)

BTW, Foldable.traverse_ also heap-allocates space linear in the size of
the map, because it is defined as
  traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
  traverse_ f = foldr ((*>) . f) (pure ())
Maybe it would be better to define it using foldMap + the appropriate
newtype? Then it would not heap-allocate, at least for Data.Map.

Cheers,
Milan




More information about the Libraries mailing list