Add foldMapM to Data.Foldable

David Feuer david.feuer at gmail.com
Thu Dec 7 01:20:32 UTC 2017


Actually, the most "natural" Applicative version is probably this:

newtype Ap f a = Ap {getAp :: f a}
instance (Applicative f, Monoid a) => Monoid (Ap f a) where
  mempty = Ap $ pure mempty
  mappend (Ap x) (Ap y) = Ap $ liftA2 mappend x y

foldMapA :: (Foldable t, Monoid m, Applicative f) => (a -> f m) -> t a -> f m
foldMapA f = getAp . foldMap (Ap . f)

Of course, we can use some Data.Coerce magic to avoid silly eta
expansion, as usual.

The "right" way to perform the actions in the opposite order is probably just

foldMapA f . Reverse

and you can accumulate the other way using getDual . foldMapA (Dual . f)

So I think the whole Applicative side of this proposal might be seen as further
motivation for my long-ago stalled proposal to add Ap to Data.Monoid.

On Wed, Dec 6, 2017 at 7:27 PM, Andrew Martin <andrew.thaddeus at gmail.com> wrote:
> I had not considered that. I tried it out on a gist
> (https://gist.github.com/andrewthad/25d1d443ec54412ae96cea3f40411e45), and
> you're definitely right. I don't understand right monadic folds well enough
> to write those out, but it would probably be worthwhile to both variants of
> it as well. Here's the code from the gist:
>
> {-# LANGUAGE ScopedTypeVariables #-}
>
> module Folds where
>
> import Control.Applicative
>
> -- Lazy in the monoidal accumulator.
> foldlMapM :: forall g b a m. (Foldable g, Monoid b, Applicative m) => (a ->
> m b) -> g a -> m b
> foldlMapM f = foldr f' (pure mempty)
>   where
>   f' :: a -> m b -> m b
>   f' x y = liftA2 mappend (f x) y
>
> -- Strict in the monoidal accumulator. For monads strict
> -- in the left argument of bind, this will run in constant
> -- space.
> foldlMapM' :: forall g b a m. (Foldable g, Monoid b, Monad m) => (a -> m b)
> -> g a -> m b
> foldlMapM' f xs = foldr f' pure xs mempty
>   where
>   f' :: a -> (b -> m b) -> b -> m b
>   f' x k bl = do
>     br <- f x
>     let !b = mappend bl br
>     k b
>
>
> On Wed, Dec 6, 2017 at 6:11 PM, David Feuer <david.feuer at gmail.com> wrote:
>>
>> It seems this lazily-accumulating version should be Applicative, and a
>> strict version Monad. Do we also need a right-to-left version of each?
>>
>> On Dec 6, 2017 9:29 AM, "Andrew Martin" <andrew.thaddeus at gmail.com> wrote:
>>
>> Several coworkers and myself have independently reinvented this function
>> several times:
>>
>>     foldMapM :: (Foldable g, Monoid b, Monad m) => (a -> m b) -> g a -> m
>> b
>>     foldMapM f xs = foldlM (\b a -> mappend b <$> (f a)) mempty xs
>>
>> I would like to propose that this be added to Data.Foldable. We have the
>> triplet foldr,foldl,foldMap in the Foldable typeclass itself, and
>> Data.Foldable provides foldrM and foldlM. It would be nice to provide
>> foldMapM for symmetry and because it seems to be useful in a variety of
>> applications.
>>
>> --
>> -Andrew Thaddeus Martin
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>
>>
>
>
>
> --
> -Andrew Thaddeus Martin


More information about the Libraries mailing list