Monoids for Maybe

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.

  • The default instance defined in Data.Monoid uses Nothing as the identity element, so Nothing represents "no information". It requires a Monoid constraint on the type wrapped by Maybe, although Monoid is slightly too strong, since the type’s own identity element is effectively ignored. In fact, the Data.Monoid documentation states

    Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s \in S." Since there is no Semigroup type class providing just mappend, we use Monoid instead.

    (Actually, there is (now) a Semigroup type class…)

    *Main> mconcat [Just (Sum 3), Nothing]
    Just (Sum {getSum = 3})
    *Main> mconcat [Just (Sum 3), Nothing, Just (Sum 4), Nothing]
    Just (Sum {getSum = 7})
    
  • The First newtype wrapper in Data.Monoid just takes the first non-Nothing occurrence:

    *Main> mconcat . map First $ [Nothing, Just 3, Nothing, Just 4]
    First {getFirst = Just 3}
    

    This is actually the same as the MonadPlus instance for Maybe, where mplus is used to choose the first non-failing computation:

    *Main Control.Monad> Nothing `mplus` 
                         Just 3 `mplus` 
                         Nothing `mplus` 
                         Just 4
    Just 3
    
  • The Last newtype wrapper is the dual of First, taking the last non-Nothing occurrence:

    *Main> mconcat . map Last $ [Nothing, Just 3, Nothing, Just 4]
    Last {getLast = Just 4}
    
  • The Monoid instance following the Applicative structure of Maybe, however, is distinct from all of these. It combines values wrapped by Just according to their own Monoid instance, but if any occurrences of Nothing are encountered, the result is also Nothing. That is, it corresponds to combining monoidal values in the presence of possible failure, that is, applying mappend idiomatically within the applicative context.

    *Main> mconcat [AM (Just (Sum 3)), AM (Just (Sum 4))]
    AM {unAM = Just (Sum {getSum = 7})}
    *Main> mconcat [AM (Just (Sum 3)), AM (Just (Sum 4)), AM Nothing]
    AM {unAM = Nothing}
    

    As far as I know, this instance is nowhere to be found in the standard libraries. Perhaps a wrapper like AM should be added to Control.Applicative?

About Brent

Associate Professor of Computer Science at Hendrix College. Functional programmer, mathematician, teacher, pianist, follower of Jesus.
This entry was posted in haskell and tagged , , , . Bookmark the permalink.

8 Responses to Monoids for Maybe

  1. Long Huynh Huu says:

    What is mempty in the latter case?

  2. Edward Kmett says:

    I called that monoid ‘App’ in my ‘monoids’ package a couple of years back.

    http://hackage.haskell.org/packages/archive/monoids/0.2.0.2/doc/html/Data-Monoid-Applicative.html

    -Edward

  3. Max says:

    @Long Huynh Huu

    It’s `Just mempty’: Just x Just mempty = Just (x mempty) = Just x; Nothing Just mempty = Nothing. And similarly it’s a left identity.

  4. Aleksey Khudyakov says:

    In fact there are 6 Monoid instances (again at least) for Maybe a. Any instance which exploit monoidal structure of a could use dual monoid as well. This makes six instances without adding much of substance.

    Also default instance of Maybe not use mempty and could be though as transformer of semigroup into monoid.

  5. beroal says:

    And we can replace Monoid with any equational algebraic theory. I.e., if
    C0 C1:cartesian monoidal category
    F:C0 monoidal→ C1
    T:equational algebraic theory
    then
    F:Mod(T,C0)→Mod(T,C1)
    my post

  6. beroal says:

    My comment is not quite correct. To make it correct, replace
    T:equational algebraic theory
    with
    T:algebraic theory with monoidal equations
    or replace
    F:C0 monoidal→ C1
    with
    F:C0 preserving products→ C1

Leave a comment

This site uses Akismet to reduce spam. Learn how your comment data is processed.