Adding foldMap implementation to instance Foldable Maybe

Eric Mertens emertens at gmail.com
Thu Jan 19 05:21:13 UTC 2017


Hello,

Independently of a blog post I just noticed tonight on reddit, http://www.snoyman.com/blog/2017/01/follow-up-mapm <http://www.snoyman.com/blog/2017/01/follow-up-mapm> I observed a stack overflow in some code I was working with due to a recursive call inside the function argument of for_

The code was a more complicated version of:

go = for_ someMaybe $ \m -> m >> go

It was wrong in thinking that this could be efficient because there’s an extra operation to set the result to a (). I thought I might try working around this with the following code.

for__ :: (Applicative f, Foldable t) => t a -> (a -> f ()) -> f ()
for__ xs f = unApp (foldMap (coerce f) xs)

newtype App f = App { unApp :: f () }

instance Applicative f => Monoid (App f) where
  mempty                  = App (pure ())
  mappend (App x) (App y) = App (x *> y)

Unfortunately the instance for Foldable for Maybe does not provide an implementation of foldMap, it only provides foldl and foldr. This means that the derived foldMap implementation attempts to mappend an extra mempty because the default implementation of foldMap is

  <>foldMap <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/Data.Foldable.html#foldMap>  <>f <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/Data.Foldable.html#local-6989586621679114983> = foldr <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/Data.Foldable.html#foldr> (mappend <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/GHC.Base.html#mappend> . <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/GHC.Base.html#.> f <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/Data.Foldable.html#local-6989586621679114983>) mempty <http://hackage.haskell.org/package/base-4.9.1.0/docs/src/GHC.Base.html#mempty>

With an explicit implementation of foldMap for the Maybe type (and maybe there are others that we’ve missed, for__ above can be stack efficient.

So I propose that we add an explicit implementation of foldMap to the Foldable Maybe instance

  foldMap _ Nothing  = mempty
  foldMap f (Just x) = f x


Best regards,
Eric Mertens
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20170118/9697c408/attachment.html>


More information about the Libraries mailing list