Proposal: add foldMapA to Data.Foldable or Control.Applicative

It's relatively easy to define foldMapA, viz. foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse I've used found it useful once so far: http://hackage.haskell.org/package/dir-traverse-0.2.0.0/docs/src/System.Dire... Cheers, Vanessa McHale

On May 8, 2019 1:56:50 AM UTC, Vanessa McHale
It's relatively easy to define foldMapA, viz.
foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse
I've used found it useful once so far: http://hackage.haskell.org/package/dir-traverse-0.2.0.0/docs/src/System.Dire...
Cheers, Vanessa McHale
Yes, please! I have found it useful on numerous occasions.

On Tue, May 7, 2019, 9:57 PM Vanessa McHale
It's relatively easy to define foldMapA, viz.
foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse
That's a bit hard for me to read. Let's rewrite it a bit: foldMapA f = fmap fold . traverse f Looking at it more plainly, I can see that this traverses the container with f, producing a bunch of values, then maps under the functor to fold them. That smells funny. Let's fix it. fold :: (Foldable f, Monoid a) => f a -> a fold = foldMap id foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m foldMapDefault f = getConst . traverse (Const . f) so foldMapA f = fmap (getConst . traverse Const) . traverse f By the functor composition law, we can write foldMapA f = fmap getConst . fmap (traverse Const) . traverse f By the traversable composition law, foldMapA f = fmap getConst . getCompose . traverse (Compose . fmap Const . f) This isn't looking so hot yet, but bear with me. fmap getConst doesn't actually do anything (it's operationally the same as fmap id = id), so we can ignore it). The functor we're traversing in is Compose f (Const b) (t x) where x can be anything. How does this functor behave? pure a = Compose (pure (pure a)) = Compose (pure (Const mempty)) liftA2 f (Compose x) (Compose y) = Compose (liftA2 (liftA2 f) x y) = Compose (liftA2 (\(Const p) (Const q) -> p <> q) x y) Whew! There are a lot of newtype wrappers, but let's ignore them. Does this Applicative instance look familiar? It should. It's operationally the same as the Monoid instance for Data.Monoid.Ap! So we can weaken Traversable to Foldable, and write foldMapA :: (Monoid b, Foldable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA f = getAp . foldMap (Ap . f) But now it's so simple I'm not sure we need to define it anymore.

TLDR: if you ever see anything that looks like
fmap (foldMap f) . traverse g
then you should generally rewrite it to
getAp . foldMap (Ap . fmap f . g)
In this case, f = id, so you just need
getAp . foldMap (Ap . g)
On Tue, May 7, 2019, 10:49 PM David Feuer
On Tue, May 7, 2019, 9:57 PM Vanessa McHale
wrote: It's relatively easy to define foldMapA, viz.
foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse
That's a bit hard for me to read. Let's rewrite it a bit:
foldMapA f = fmap fold . traverse f
Looking at it more plainly, I can see that this traverses the container with f, producing a bunch of values, then maps under the functor to fold them. That smells funny. Let's fix it.
fold :: (Foldable f, Monoid a) => f a -> a fold = foldMap id
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m foldMapDefault f = getConst . traverse (Const . f)
so
foldMapA f = fmap (getConst . traverse Const) . traverse f
By the functor composition law, we can write
foldMapA f = fmap getConst . fmap (traverse Const) . traverse f
By the traversable composition law,
foldMapA f = fmap getConst . getCompose . traverse (Compose . fmap Const . f)
This isn't looking so hot yet, but bear with me. fmap getConst doesn't actually do anything (it's operationally the same as fmap id = id), so we can ignore it). The functor we're traversing in is
Compose f (Const b) (t x)
where x can be anything. How does this functor behave?
pure a = Compose (pure (pure a)) = Compose (pure (Const mempty))
liftA2 f (Compose x) (Compose y) = Compose (liftA2 (liftA2 f) x y) = Compose (liftA2 (\(Const p) (Const q) -> p <> q) x y)
Whew! There are a lot of newtype wrappers, but let's ignore them. Does this Applicative instance look familiar? It should. It's operationally the same as the Monoid instance for Data.Monoid.Ap! So we can weaken Traversable to Foldable, and write
foldMapA :: (Monoid b, Foldable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA f = getAp . foldMap (Ap . f)
But now it's so simple I'm not sure we need to define it anymore.

My second to last comment was potentially non-optimal in unusual cases. If
fmap is sufficiently expensive for the functor in question, and f is not
id, then you might want to use
import Data.Functor.Coyoneda
lowerCoyoneda . getAp . foldMap (Ap . fmap f . liftCoyoneda . g)
This is pretty similar to the composition of foldMap and traverse, but it
doesn't have a Traversable constraint.
On Tue, May 7, 2019, 10:59 PM David Feuer
TLDR: if you ever see anything that looks like
fmap (foldMap f) . traverse g
then you should generally rewrite it to
getAp . foldMap (Ap . fmap f . g)
In this case, f = id, so you just need
getAp . foldMap (Ap . g)
On Tue, May 7, 2019, 10:49 PM David Feuer
wrote: On Tue, May 7, 2019, 9:57 PM Vanessa McHale
wrote: It's relatively easy to define foldMapA, viz.
foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse
That's a bit hard for me to read. Let's rewrite it a bit:
foldMapA f = fmap fold . traverse f
Looking at it more plainly, I can see that this traverses the container with f, producing a bunch of values, then maps under the functor to fold them. That smells funny. Let's fix it.
fold :: (Foldable f, Monoid a) => f a -> a fold = foldMap id
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m foldMapDefault f = getConst . traverse (Const . f)
so
foldMapA f = fmap (getConst . traverse Const) . traverse f
By the functor composition law, we can write
foldMapA f = fmap getConst . fmap (traverse Const) . traverse f
By the traversable composition law,
foldMapA f = fmap getConst . getCompose . traverse (Compose . fmap Const . f)
This isn't looking so hot yet, but bear with me. fmap getConst doesn't actually do anything (it's operationally the same as fmap id = id), so we can ignore it). The functor we're traversing in is
Compose f (Const b) (t x)
where x can be anything. How does this functor behave?
pure a = Compose (pure (pure a)) = Compose (pure (Const mempty))
liftA2 f (Compose x) (Compose y) = Compose (liftA2 (liftA2 f) x y) = Compose (liftA2 (\(Const p) (Const q) -> p <> q) x y)
Whew! There are a lot of newtype wrappers, but let's ignore them. Does this Applicative instance look familiar? It should. It's operationally the same as the Monoid instance for Data.Monoid.Ap! So we can weaken Traversable to Foldable, and write
foldMapA :: (Monoid b, Foldable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA f = getAp . foldMap (Ap . f)
But now it's so simple I'm not sure we need to define it anymore.

I've previously suggested similar things, like:
allA :: (Applicative f, Foldable t) => (a -> f Bool) -> t a -> f Bool
allA f = fmap getAll . getAp . foldMap (Ap . fmap All . f)
I think such functions are very convenient.
On Wed, 8 May 2019, 1:37 pm David Feuer,
My second to last comment was potentially non-optimal in unusual cases. If fmap is sufficiently expensive for the functor in question, and f is not id, then you might want to use
import Data.Functor.Coyoneda
lowerCoyoneda . getAp . foldMap (Ap . fmap f . liftCoyoneda . g)
This is pretty similar to the composition of foldMap and traverse, but it doesn't have a Traversable constraint.
On Tue, May 7, 2019, 10:59 PM David Feuer
wrote: TLDR: if you ever see anything that looks like
fmap (foldMap f) . traverse g
then you should generally rewrite it to
getAp . foldMap (Ap . fmap f . g)
In this case, f = id, so you just need
getAp . foldMap (Ap . g)
On Tue, May 7, 2019, 10:49 PM David Feuer
wrote: On Tue, May 7, 2019, 9:57 PM Vanessa McHale
wrote: It's relatively easy to define foldMapA, viz.
foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse
That's a bit hard for me to read. Let's rewrite it a bit:
foldMapA f = fmap fold . traverse f
Looking at it more plainly, I can see that this traverses the container with f, producing a bunch of values, then maps under the functor to fold them. That smells funny. Let's fix it.
fold :: (Foldable f, Monoid a) => f a -> a fold = foldMap id
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m foldMapDefault f = getConst . traverse (Const . f)
so
foldMapA f = fmap (getConst . traverse Const) . traverse f
By the functor composition law, we can write
foldMapA f = fmap getConst . fmap (traverse Const) . traverse f
By the traversable composition law,
foldMapA f = fmap getConst . getCompose . traverse (Compose . fmap Const . f)
This isn't looking so hot yet, but bear with me. fmap getConst doesn't actually do anything (it's operationally the same as fmap id = id), so we can ignore it). The functor we're traversing in is
Compose f (Const b) (t x)
where x can be anything. How does this functor behave?
pure a = Compose (pure (pure a)) = Compose (pure (Const mempty))
liftA2 f (Compose x) (Compose y) = Compose (liftA2 (liftA2 f) x y) = Compose (liftA2 (\(Const p) (Const q) -> p <> q) x y)
Whew! There are a lot of newtype wrappers, but let's ignore them. Does this Applicative instance look familiar? It should. It's operationally the same as the Monoid instance for Data.Monoid.Ap! So we can weaken Traversable to Foldable, and write
foldMapA :: (Monoid b, Foldable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA f = getAp . foldMap (Ap . f)
But now it's so simple I'm not sure we need to define it anymore.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Tue, May 7, 2019 at 11:49 PM Isaac Elliott
I've previously suggested similar things, like:
allA :: (Applicative f, Foldable t) => (a -> f Bool) -> t a -> f Bool allA f = fmap getAll . getAp . foldMap (Ap . fmap All . f)
I think such functions are very convenient.
I think your allA is arguably better-justified than foldMapA because the simple implementation you demonstrate could run into trouble if fmap is expensive. Better: allA :: (Applicative f, Foldable t) => (a -> f Bool) -> t a -> f Bool allA f = getFall . foldMap (Fall . f) newtype Fall f = Fall {getFall :: f Bool} instance Applicative f => Semigroup (Fall f) where Fall x <> Fall y = Fall $ liftA2 (&&) x y instance Applicative f => Monoid (Fall f) where mempty = Fall (pure True) I keep wondering if there's some nice way (short of Coyoneda or similar) to generalize this sort of thing. I haven't thought of one yet.

Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a
working programmer I know exactly what Applicative, Traversable, and Monoid
are (from Vanessa's original proposal), but the unfortunately-named getAp
is something I will only learn about begrudgingly.
What you consider "so simple we don't need to define it" took a rather
lengthy email to describe. Are you sure it's not worth actually defining?
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone
like me to peer beneath the hood and learn something new.
On Wed, 8 May 2019, 5.59 David Feuer,
TLDR: if you ever see anything that looks like
fmap (foldMap f) . traverse g
then you should generally rewrite it to
getAp . foldMap (Ap . fmap f . g)
In this case, f = id, so you just need
getAp . foldMap (Ap . g)
On Tue, May 7, 2019, 10:49 PM David Feuer
wrote: On Tue, May 7, 2019, 9:57 PM Vanessa McHale
wrote: It's relatively easy to define foldMapA, viz.
foldMapA :: (Monoid b, Traversable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA = (fmap fold .) . traverse
That's a bit hard for me to read. Let's rewrite it a bit:
foldMapA f = fmap fold . traverse f
Looking at it more plainly, I can see that this traverses the container with f, producing a bunch of values, then maps under the functor to fold them. That smells funny. Let's fix it.
fold :: (Foldable f, Monoid a) => f a -> a fold = foldMap id
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m foldMapDefault f = getConst . traverse (Const . f)
so
foldMapA f = fmap (getConst . traverse Const) . traverse f
By the functor composition law, we can write
foldMapA f = fmap getConst . fmap (traverse Const) . traverse f
By the traversable composition law,
foldMapA f = fmap getConst . getCompose . traverse (Compose . fmap Const . f)
This isn't looking so hot yet, but bear with me. fmap getConst doesn't actually do anything (it's operationally the same as fmap id = id), so we can ignore it). The functor we're traversing in is
Compose f (Const b) (t x)
where x can be anything. How does this functor behave?
pure a = Compose (pure (pure a)) = Compose (pure (Const mempty))
liftA2 f (Compose x) (Compose y) = Compose (liftA2 (liftA2 f) x y) = Compose (liftA2 (\(Const p) (Const q) -> p <> q) x y)
Whew! There are a lot of newtype wrappers, but let's ignore them. Does this Applicative instance look familiar? It should. It's operationally the same as the Monoid instance for Data.Monoid.Ap! So we can weaken Traversable to Foldable, and write
foldMapA :: (Monoid b, Foldable t, Applicative f) => (a -> f b) -> t a -> f b foldMapA f = getAp . foldMap (Ap . f)
But now it's so simple I'm not sure we need to define it anymore.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet. If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one?

I would like to add one more point of reference to the discussion. The `foldMapA` function is also implemented in the `relude` alternative prelude: http://hackage.haskell.org/package/relude-0.5.0/docs/src/Relude.Foldable.Fol... And the implementation already uses `Ap` and `getAp` as was discussed here. Previous implementation used `fmap` and `traverse` but it was changed to a more efficient one. One possible improvement: instead of current implementation
foldMapA f = getAp . foldMap (Ap . f)
It can be slightly more efficient (I guess) by using #. operator to coerce newtypes
foldMapA f = getAp #. foldMap (Ap . f)
The implementation in `relude` also contains recommended order of variables
under `forall`. After using `foldMapA` in production for a while we've
figured out in what order variables should go to resolve most often
ambiguities via TypeApplication.
On Wed, May 8, 2019 at 12:36 PM David Feuer
On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I appreciate the more efficient version, but I do not consider a package like relude to be an alternative to base (due to dependencies, maintenance). On 5/8/19 10:50 PM, Dmitriy Kovanikov wrote:
I would like to add one more point of reference to the discussion. The `foldMapA` function is also implemented in the `relude` alternative prelude:
http://hackage.haskell.org/package/relude-0.5.0/docs/src/Relude.Foldable.Fol...
And the implementation already uses `Ap` and `getAp` as was discussed here. Previous implementation used `fmap` and `traverse` but it was changed to a more efficient one.
One possible improvement: instead of current implementation
foldMapA f = getAp . foldMap (Ap . f)
It can be slightly more efficient (I guess) by using #. operator to coerce newtypes
foldMapA f = getAp #. foldMap (Ap . f)
The implementation in `relude` also contains recommended order of variables under `forall`. After using `foldMapA` in production for a while we've figured out in what order variables should go to resolve most often ambiguities via TypeApplication.
On Wed, May 8, 2019 at 12:36 PM David Feuer
mailto:david.feuer@gmail.com> wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter mailto:b@chreekat.net> wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Vanessa, it's very common for discussions about adding things to base (or
containers, etc) to get into how those matters have been handled elsewhere.
Many people think that it's better to pull ideas into base only after
they've demonstrated their value elsewhere. Dmitriy's comment should
definitely not be taken as criticism of your proposal.
Dmitriy, there's no question that (#.) or similar should be used rather
than (.). I didn't mention that because it doesn't seem to bear on the
overall question of whether the function should be added, and I didn't want
to confuse other participants with semi-obscure coercion operators.
On Thu, May 9, 2019, 10:28 AM Vanessa McHale
I appreciate the more efficient version, but I do not consider a package like relude to be an alternative to base (due to dependencies, maintenance). On 5/8/19 10:50 PM, Dmitriy Kovanikov wrote:
I would like to add one more point of reference to the discussion. The `foldMapA` function is also implemented in the `relude` alternative prelude:
http://hackage.haskell.org/package/relude-0.5.0/docs/src/Relude.Foldable.Fol...
And the implementation already uses `Ap` and `getAp` as was discussed here. Previous implementation used `fmap` and `traverse` but it was changed to a more efficient one.
One possible improvement: instead of current implementation
foldMapA f = getAp . foldMap (Ap . f)
It can be slightly more efficient (I guess) by using #. operator to coerce newtypes
foldMapA f = getAp #. foldMap (Ap . f)
The implementation in `relude` also contains recommended order of variables under `forall`. After using `foldMapA` in production for a while we've figured out in what order variables should go to resolve most often ambiguities via TypeApplication.
On Wed, May 8, 2019 at 12:36 PM David Feuer
wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing listLibraries@haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Vanessa, I'm not proposing to replace base with relude in libraries like
dir-traverse. Sorry if I wasn't clear enough, I didn't mean to introduce
more confusion.
I don't use `relude` in my libraries as well because I prefer a low amount
of external dependencies and I usually use alternative prelude only in big
applications.
As David mentioned, I indeed just wanted to show one more place where
`foldMapA` is introduced because it's not in base. Having `foldMapA` in
base will make `relude` even better because it will have even fewer custom
things in favour of mere reexports from base. I also think that if some
data type / function has already been in some alternative prelude for some
time, it could be a good addition to base.
On Thu, May 9, 2019 at 10:28 PM Vanessa McHale
I appreciate the more efficient version, but I do not consider a package like relude to be an alternative to base (due to dependencies, maintenance). On 5/8/19 10:50 PM, Dmitriy Kovanikov wrote:
I would like to add one more point of reference to the discussion. The `foldMapA` function is also implemented in the `relude` alternative prelude:
http://hackage.haskell.org/package/relude-0.5.0/docs/src/Relude.Foldable.Fol...
And the implementation already uses `Ap` and `getAp` as was discussed here. Previous implementation used `fmap` and `traverse` but it was changed to a more efficient one.
One possible improvement: instead of current implementation
foldMapA f = getAp . foldMap (Ap . f)
It can be slightly more efficient (I guess) by using #. operator to coerce newtypes
foldMapA f = getAp #. foldMap (Ap . f)
The implementation in `relude` also contains recommended order of variables under `forall`. After using `foldMapA` in production for a while we've figured out in what order variables should go to resolve most often ambiguities via TypeApplication.
On Wed, May 8, 2019 at 12:36 PM David Feuer
wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing listLibraries@haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Its a complicated landscape, and we're still learning.
if a new combinator is hard to write:
a) how do we help educate folks into seeing it as an easy combinator
b) what are the with/without fusion cost models of different
implementations?
c) is it useful?
I’m slightly inclined to support inclusion.
One question I have is whether it’s definable via foldmap itself ?
On Wed, May 8, 2019 at 12:36 AM David Feuer
On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Carter, I already showed that it is, and Dmitriy already refined that
definition.
On Thu, May 9, 2019, 10:35 AM Carter Schonwald
Its a complicated landscape, and we're still learning.
if a new combinator is hard to write: a) how do we help educate folks into seeing it as an easy combinator b) what are the with/without fusion cost models of different implementations? c) is it useful?
I’m slightly inclined to support inclusion.
One question I have is whether it’s definable via foldmap itself ?
On Wed, May 8, 2019 at 12:36 AM David Feuer
wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

derp, the Ap newtype for getting a monoid from aplicative f over monoid
On Thu, May 9, 2019 at 10:38 AM David Feuer
Carter, I already showed that it is, and Dmitriy already refined that definition.
On Thu, May 9, 2019, 10:35 AM Carter Schonwald
wrote: Its a complicated landscape, and we're still learning.
if a new combinator is hard to write: a) how do we help educate folks into seeing it as an easy combinator b) what are the with/without fusion cost models of different implementations? c) is it useful?
I’m slightly inclined to support inclusion.
One question I have is whether it’s definable via foldmap itself ?
On Wed, May 8, 2019 at 12:36 AM David Feuer
wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I've personally defined `foldMapA` in at least three private projects, and
I've one-off written it probably over a dozen times. Each time I've used
something like `fmap k . traverse f` where `k` is one of `mconcat`, `fold`,
`join`, etc. I appreciate the subtle discussion on the implementation for
performance and I think it'd be awesome to have this defined in `base`.
Matt Parsons
On Tue, May 7, 2019 at 10:36 PM David Feuer
On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I've also defined this in multiple of my own projects/codebases, and I
provided it as a motivation for introducing Data.Monoid.Ap in the first
place.
I'm +1 on the inclusion of foldMapA.
On Thu, May 9, 2019, 11:10 AM Matt
I've personally defined `foldMapA` in at least three private projects, and I've one-off written it probably over a dozen times. Each time I've used something like `fmap k . traverse f` where `k` is one of `mconcat`, `fold`, `join`, etc. I appreciate the subtle discussion on the implementation for performance and I think it'd be awesome to have this defined in `base`.
Matt Parsons
On Tue, May 7, 2019 at 10:36 PM David Feuer
wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Interestingly, in the case of dir-traverse, foldMapA = (fmap fold .) . traverse ends up being faster than foldMapA f = getAp . foldMap (Ap . f) ...which I did not expect. I suppose we should benchmark this before adding it to base. Cheers, Vanessa McHale On 5/9/19 12:49 PM, chessai . wrote:
I've also defined this in multiple of my own projects/codebases, and I provided it as a motivation for introducing Data.Monoid.Ap in the first place.
I'm +1 on the inclusion of foldMapA.
On Thu, May 9, 2019, 11:10 AM Matt
mailto:parsonsmatt@gmail.com> wrote: I've personally defined `foldMapA` in at least three private projects, and I've one-off written it probably over a dozen times. Each time I've used something like `fmap k . traverse f` where `k` is one of `mconcat`, `fold`, `join`, etc. I appreciate the subtle discussion on the implementation for performance and I think it'd be awesome to have this defined in `base`.
Matt Parsons
On Tue, May 7, 2019 at 10:36 PM David Feuer
mailto:david.feuer@gmail.com> wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter mailto:b@chreekat.net> wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

That's ... surprising. I'm quite curious what exactly you tried. Did you
compile with optimizations? I see that in the Hackage version, foldMapA is
defined in a where clause of a recursive function. I wouldn't be surprised
if that could cause some trouble, especially if optimizations are disabled.
Side note: I doubt you're actually winning anything significant by having a
special case for [].
On Thu, May 9, 2019, 2:56 PM Vanessa McHale
Interestingly, in the case of dir-traverse,
foldMapA = (fmap fold .) . traverse
ends up being faster than
foldMapA f = getAp . foldMap (Ap . f)
...which I did not expect. I suppose we should benchmark this before adding it to base.
Cheers, Vanessa McHale On 5/9/19 12:49 PM, chessai . wrote:
I've also defined this in multiple of my own projects/codebases, and I provided it as a motivation for introducing Data.Monoid.Ap in the first place.
I'm +1 on the inclusion of foldMapA.
On Thu, May 9, 2019, 11:10 AM Matt
wrote: I've personally defined `foldMapA` in at least three private projects, and I've one-off written it probably over a dozen times. Each time I've used something like `fmap k . traverse f` where `k` is one of `mconcat`, `fold`, `join`, etc. I appreciate the subtle discussion on the implementation for performance and I think it'd be awesome to have this defined in `base`.
Matt Parsons
On Tue, May 7, 2019 at 10:36 PM David Feuer
wrote: On Wed, May 8, 2019, 12:12 AM Bryan Richter wrote:
Hi David,
At the risk of invoking the gods of Language Blorp, I will note that as a working programmer I know exactly what Applicative, Traversable, and Monoid are (from Vanessa's original proposal), but the unfortunately-named getAp is something I will only learn about begrudgingly.
That seems unfortunate. Learning to use such types is pretty useful. I'd recommend that every Haskell programmer get to know all the types in Data.Monoid and come to an understanding of what they're good for.
What you consider "so simple we don't need to define it" took a rather lengthy email to describe. Are you sure it's not worth actually defining?
So ... that long post was about trying to prove what I intuitively thought *must* be true. In the end, I wasn't quite able to finish the proof, but I did at least manage to convince myself that my intuition was correct. It's true that this sort of intuition takes a certain amount of time to develop. In the case of a really important operation, yeah, we should package it up. But is this operation important enough? I'm not really convinced yet.
If nothing else, the next time someone searches Hoogle for a function
matching its type signature, perhaps it will be an opportunity for someone like me to peer beneath the hood and learn something new.
That's valid. But ... there are lots of opportunities for that sort of thing already. Is it worth the API clutter to add another one? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing listLibraries@haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (9)
-
Bryan Richter
-
Carter Schonwald
-
chessai .
-
David Feuer
-
Dmitriy Kovanikov
-
Isaac Elliott
-
Lana Black
-
Matt
-
Vanessa McHale