
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