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

Isaac Elliott isaace71295 at gmail.com
Wed May 8 03:49:48 UTC 2019


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, <david.feuer at gmail.com> wrote:

> 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 <david.feuer at gmail.com> 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 <david.feuer at gmail.com> wrote:
>>
>>> On Tue, May 7, 2019, 9:57 PM Vanessa McHale <vanessa.mchale at iohk.io>
>>> 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 at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190508/43d2ad32/attachment.html>


More information about the Libraries mailing list