Discussion:
Add foldMapM to Data.Foldable
Andrew Martin
2017-12-06 14:28:37 UTC
Permalink
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
Andreas Abel
2017-12-06 23:04:02 UTC
Permalink
+1.

If I remember correctly, then Henning Thielemann has suggested this as
the proper generalization of mapM_.
Post by Andrew Martin
Several coworkers and myself have independently reinvented this function
    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
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
--
Andreas Abel <>< Du bist der geliebte Mensch.

Department of Computer Science and Engineering
Chalmers and Gothenburg University, Sweden

***@gu.se
http://www.cse.chalmers.se/~abela/
David Feuer
2017-12-06 23:11:07 UTC
Permalink
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" <***@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
Andrew Martin
2017-12-07 00:27:43 UTC
Permalink
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
Post by David Feuer
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?
Several coworkers and myself have independently reinvented this function
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
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
--
-Andrew Thaddeus Martin
David Feuer
2017-12-07 01:20:32 UTC
Permalink
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.
Post by Andrew Martin
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
{-# 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
Post by David Feuer
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?
Several coworkers and myself have independently reinvented this function
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
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
--
-Andrew Thaddeus Martin
David Feuer
2017-12-07 04:15:44 UTC
Permalink
Actually, the key modifiers are probably Dual and Backwards, with Reverse
combining them. Or something like that.
Post by David Feuer
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.
Post by Andrew Martin
I had not considered that. I tried it out on a gist
(https://gist.github.com/andrewthad/25d1d443ec54412ae96cea3f40411e45),
and
Post by Andrew Martin
you're definitely right. I don't understand right monadic folds well
enough
Post by Andrew Martin
to write those out, but it would probably be worthwhile to both variants
of
Post by Andrew Martin
{-# 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
->
Post by Andrew Martin
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)
Post by Andrew Martin
-> 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
Post by David Feuer
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?
Several coworkers and myself have independently reinvented this function
foldMapM :: (Foldable g, Monoid b, Monad m) => (a -> m b) -> g a ->
m
Post by Andrew Martin
Post by David Feuer
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
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
--
-Andrew Thaddeus Martin
David Feuer
2017-12-07 21:04:18 UTC
Permalink
Indeed,

f g = g (\x -> putStr x >> pure x) ["hi", "I'm", "Bob"]

f foldMapA = f $ \g -> getAp . foldMap (Ap . g)
prints "hiI'mBob" and returns "hiI'mBob"
f (\g -> forwards . foldMayO (Backwards . g))
= f (\g -> forwards . getAp . foldMap (Ap . Backwards . g))
prints "BobI'mhi" and returns "hiI'mBob"
f (\g -> fmap getDual . foldMapA (fmap Dual . g))
= f (\g -> fmap getDual . foldMap (Ap . fmap Dual . g))
prints "hiI'mBob" and returns "BobI'mHi"
f (\g -> foldMapA g . Reverse)
= f (\g -> getAp . getDual . foldMap (Dual . Ap . g)
prints "BobI'mHi" and returns "BobI'mHi"

None of this affects the strict (monadic) versions, which should be defined in
terms of foldr and foldl. It's not entirely clear to me which way those monadic
versions should accumulate.
Post by David Feuer
Actually, the key modifiers are probably Dual and Backwards, with Reverse
combining them. Or something like that.
Post by David Feuer
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.
Post by Andrew Martin
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
{-# 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
Post by David Feuer
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?
Several coworkers and myself have independently reinvented this function
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
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
--
-Andrew Thaddeus Martin
Loading...