« Call for contributions: second edition of the Typeclassopedia » Themes on Streams

Monoids for Maybe

Posted on April 18, 2011
Tagged , , ,

The other day I had two lists of monoidal values that I wanted to combine in a certain way, and I realized it was an instance of this more general pattern:

> {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> import Data.Monoid
> import Control.Applicative
> 
> (<>) :: Monoid m => m -> m -> m
> (<>) = mappend   -- I can't stand writing `mappend`
> 
> newtype AM f m = AM { unAM :: f m }
>   deriving (Functor, Applicative, Show)
> 
> instance (Applicative f, Monoid m) => Monoid (AM f m) where
>   mempty        = pure mempty
>   mappend f1 f2 = mappend <$> f1 <*> f2

It’s not too hard (although a bit fiddly) to show that AM f m satisfies the monoid laws, given that f and m satisfy the applicative functor and monoid laws respectively.

The basic idea here is that the mappend operation for AM f m is just the mappend operation for m, but applied "idiomatically" in the f context. For example, when f = [], this combines two lists of monoidal values by combining all possible pairs:

*Main> map getProduct . unAM $ (AM (map Product [1,2,3]) 
                                <> AM (map Product [1,10,100]))
[1,10,100,2,20,200,3,30,300]

In the #haskell IRC channel someone pointed out to me that Data.Monoid has an instance Monoid m => Monoid (e -> m) which is just a special case of this pattern:

*Main> :m +Data.Ord
*Main Data.Ord> map ((unAM $ AM (comparing length) 
                             <> AM compare) "foo") 
                    ["ba", "bar", "barr"]
[GT,GT,LT]
*Main Data.Ord> map ((comparing length <> compare) "foo") 
                    ["ba", "bar", "barr"]
[GT,GT,LT]

It was also mentioned that the monoid instance for Maybe is also a special case of this pattern:

*Main> AM (Just (Sum 3)) <> AM Nothing
AM {unAM = Nothing}
*Main> Just (Sum 3) <> Nothing
Just (Sum {getSum = 3})

Wait, hold on, what?! It turns out that the default Monoid instance for Maybe is not an instance of this pattern after all! I previously thought there were three different ways of declaring a Monoid instance for Maybe; I now know that there are (at least) four.