Haskell/Monoids

From Wikibooks, open books for an open world
Jump to navigation Jump to search

In earlier parts of the book, we have made a few passing allusions to monoids and the Monoid type class (most notably when discussing MonadPlus). Here we'll give them a more detailed look and show what makes them useful.

What is a monoid?[edit | edit source]

The operation of adding numbers has a handful of properties which are so elementary we don't even think about them when summing numbers up. One of them is associativity: when adding three or more numbers it doesn't matter how we group the terms.

GHCi> (5 + 6) + 10
21
GHCi> 5 + (6 + 10)
21

Another one is that it has an identity element, which can be added to any other number without changing its value. That element is the number zero:

GHCi> 255 + 0
255
GHCi> 0 + 255
255

Addition is not the only binary operation which is associative and has an identity element. Multiplication does too, albeit with a different identity.

GHCi> (5 * 6) * 10
300
GHCi> 5 * (6 * 10)
300
GHCi> 255 * 1
255
GHCi> 1 * 255
255

We needn't restrict ourselves to arithmetic either. (++), the appending operation for Haskell lists, is another example. It has the empty list as its identity element.

GHCi> ([1,2,3] ++ [4,5,6]) ++ [7,8,9]
[1,2,3,4,5,6,7,8,9]
GHCi> [1,2,3] ++ ([4,5,6] ++ [7,8,9])
[1,2,3,4,5,6,7,8,9]
GHCi> [1,2,3] ++ []
[1,2,3]
GHCi> [] ++ [1,2,3]
[1,2,3]

It turns out there are a great many associative binary operations with an identity. All of them, by definition, give us examples of monoids. We say, for instance, that the integer numbers form a monoid under addition with 0 as identity element.

The Monoid class[edit | edit source]

Monoids show up very often in Haskell, and so it is not surprising to find there is a type class for them in the core libraries. Here it is:

class Monoid a where
    mempty  :: a
    mappend :: a -> a -> a

    mconcat :: [a] -> a
    mconcat = foldr mappend mempty

The mappend method is the binary operation, and mempty is its identity. The third method, mconcat, is provided as a bonus; it runs down a list and mappends its elements together in order.

"mappend" is a somewhat long and unwieldy name for a binary function so general, even more so for one which is often used infix. Fortunately, Data.Monoid Data.Monoid provides (<>), a convenient operator synonym for mappend. In what follows, we will use mappend and (<>) interchangeably.

As an example, this is the monoid instance for lists:

instance Monoid [a] where
    mempty  = []
    mappend = (++)

Note that, in this case, mconcat = foldr (++) [] is equivalent to concat, which explains the name of the method.

It is legitimate to think of monoids as types which support appending in some sense, though a dose of poetic licence is required. The Monoid definition is extremely general and not at all limited to data structures, so "appending" will be just a metaphor at times.

As we suggested earlier on, numbers (i.e. instances of Num) form monoids under both addition and multiplication. That leads to the awkward question of which one to choose when writing the instance. In situations like this one, in which there is no good reason to choose one possibility over the other, the dilemma is averted by creating one newtype for each instance:

-- | Monoid under addition.
newtype Sum a = Sum { getSum :: a }

-- | Monoid under multiplication.
newtype Product a = Product { getProduct :: a }

instance Num a => Monoid (Sum a) where
    mempty = Sum 0
    Sum x `mappend` Sum y = Sum (x + y)

instance Num a => Monoid (Product a) where
    mempty = Product 1
    Product x `mappend` Product y = Product (x * y)

Here is a quick demonstration of Sum and Product:

GHCi> import Data.Monoid
GHCi> Sum 5 <> Sum 6 <> Sum 10
Sum {getSum = 21}
GHCi> mconcat [Sum 5, Sum 6, Sum 10]
Sum {getSum = 21}
GHCi> getSum . mconcat . fmap Sum $ [5, 6, 10]
21
GHCi> getProduct . mconcat . fmap Product $ [5, 6, 10]
300

Monoid laws[edit | edit source]

The laws which all instances of Monoid must follow simply state the properties we already know: mappend is associative and mempty is its identity element.

(x <> y) <> z = x <> (y <> z) -- associativity
mempty <> x = x               -- left identity
x <> mempty = x               -- right identity
Exercises
  1. There are several possible monoid instances for Bool. Write at least two of them using newtypes, as in the Sum and Product examples. Be sure to verify the monoid laws hold for your instances [1].

Uses[edit | edit source]

Which advantages are there in having a class with a pompous name for such a simple concept? As usual in such cases, the key gains are in two associated dimensions: recognisability and generality. Whenever, for instance, you see (<>) being used you know that, however the specific instance was defined, the operation being done is associative and has an identity element. Moreover, you also know that if there is an instance of Monoid for a type you can take advantage of functions written to deal with monoids in general. As a toy example of such a function, we might take this function that concatenates three lists..

threeConcat :: [a] -> [a] -> [a] -> [a]
threeConcat a b c = a ++ b ++ c

... and replace all (++) with (<>)...

mthreeConcat :: Monoid m => m -> m -> m -> m
mthreeConcat a b c = a <> b <> c

... thus making it work with any Monoid. When used on other types the generalised function will behave in an analogous way to the original one, as specified by the monoid laws.

GHCi> mthreeConcat "Hello" " " "world!"
"Hello world!"
GHCi> mthreeConcat (Sum 5) (Sum 6) (Sum 10)
Sum {getSum = 21}

Monoids are extremely common, and have many interesting practical applications.

The Writer monad
A computation of type Writer w a computes a value of type a while producing extra output of type w which must be an instance of Monoid, and the bind operator of the monad uses mappend to accumulate the extra output. A typical use case would be logging, in which each computation produces a log entry for later inspection. In the logging use case, that would mean all entries generated during a series of computations are automatically combined into a single log output.
The Foldable class
Monoids play an important role in generalising list-like folding to other data structures. We will study that in detail in the upcoming chapter about the Foldable class.
Finger trees
Moving on from operations on data structures to data structure implementations, monoids can be used to implement finger trees, an efficient and versatile data structure. Its implementation makes use of monoidal values as tags for the tree nodes; and different data structures (such as sequences, priority queues, and search trees) can be obtained simply by changing the involved Monoid instance.[2]
Options and settings
In a wholly different context, monoids can be a handy way of treating application options and settings. Two examples are Cabal, the Haskell packaging system ("Package databases are monoids. Configuration files are monoids. Command line flags and sets of command line flags are monoids. Package build information is a monoid.") and XMonad, a tiling window manager implemented in Haskell ("xmonad configuration hooks are monoidal.") [3]. Below are snippets from a XMonad configuration file (which is just a Haskell program) showing the monoidal hooks in action [4].
-- A ManageHook is a rule, or a combination of rules, for
-- automatically handling specific kinds of windows. It
-- is applied on window creation.

myManageHook :: ManageHook
myManageHook = composeAll
    [ manageConkeror
    , manageDocs
    , manageEmacs
    , manageGimp
    , manageImages
    , manageTerm
    , manageTransient
    , manageVideo
    , manageWeb
    , myNSManageHook scratchpads
    ]

-- manageEmacs, for instance, makes a duplicate of an Emacs
-- window in workspace 3 and sets its opacity to 90%. It
-- looks like this:

-- liftX lifts a normal X action into a Query (as expected by -->)
-- idHook ensures the proper return type
manageEmacs :: ManageHook
manageEmacs =
    className =? "Emacs"
    --> (ask >>= doF . \w -> (copyWindow w "3:emacs"))
    <+> (ask >>= \w -> liftX (setOpacity w 0.9) >> idHook)

-- The hooks are used as fields of the XMonad configuration,
-- which is passed to the IO action that starts XMonad.

myConfig xmproc = defaultConfig
                  { -- Among other fields...
                  , manageHook         = myManageHook
                  } 

-- idHook, (<+>), composeAll and (-->) are just user-friendly
-- synonyms for monoid operations, defined in the
-- XMonad.ManageHook module thusly:

-- | The identity hook that returns the WindowSet unchanged.
idHook :: Monoid m => m
idHook = mempty

-- | Infix 'mappend'. Compose two 'ManageHook' from right to left.
(<+>) :: Monoid m => m -> m -> m
(<+>) = mappend

-- | Compose the list of 'ManageHook's.
composeAll :: Monoid m => [m] -> m
composeAll = mconcat

-- | @p --> x@.  If @p@ returns 'True', execute the 'ManageHook'.
--
-- > (-->) :: Monoid m => Query Bool -> Query m -> Query m -- a simpler type
(-->) :: (Monad m, Monoid a) => m Bool -> m a -> m a
p --> f = p >>= \b -> if b then f else return mempty
A simple diagrams example. The code for it is:
mconcat  (fmap
  (circle . (/20)) [1..5])
<> triangle (sqrt 3 / 2)
  # lwL 0.01 # fc yellow 
<> circle 0.5 # lwL 0.02
  # fc deepskyblue
diagrams
The diagrams package provides a powerful library for generating vectorial images programatically. On a basic level, (<>) appears often in code using diagrams because squares, rectangles and other such graphic elements have Monoid instances which are used to put them on the top of each other. On a deeper level, most operations with graphic elements are internally defined in terms of monoids, and the implementation takes full advantage of their mathematical properties.

Homomorphisms[edit | edit source]

Given any two monoids A and B, a function f :: A -> B is a monoid homomorphism if it preserves the monoid structure, so that:

f mempty          = mempty
f (x `mappend` y) = f x `mappend` f y

In words, f takes mempty :: A to mempty :: B, and the result of mappend for A to the result of mappend for B (after using f to turn the arguments to mappend into B values).

As an example, length is a monoid homomorphism between ([a],++) and (Int,+):

length []         = 0
length (xs ++ ys) = length xs + length ys

When attempting to determine if a given function is a homomorphism do not concern yourself with the actual implementation; although its definition clearly influences whether or not it is a homomorphism, a homomorphism is defined by a function's ability to preserve the operations of the two underlying structures involved in the mapping and is not directly tied to implementation details.

An interesting example "in the wild" of monoids and homomorphisms was identified by Chris Kuklewicz amidst the Google Protocol Buffers API documentation.[5] Based on the quotes provided in the referenced comment, we highlight that the property that (in C++):

MyMessage message;
message.ParseFromString(str1 + str2);

... is equivalent to...

MyMessage message, message2;
message.ParseFromString(str1);
message2.ParseFromString(str2);
message.MergeFrom(message2);

... means that ParseFromString is a monoid homomorphism. In a hypothetical Haskell implementation, the following equations would hold:

parse :: String -> Message
-- these are just equations, not actual code.
parse []         = mempty
parse (xs ++ ys) = parse xs `mergeFrom` parse ys

(They wouldn't hold perfectly, as parsing might fail, but roughly so.)

Recognising a homomorphism can lead to useful refactorings. For instance, if mergeFrom turned out to be an expensive operation it might be advantageous in terms of performance to concatenate the strings before parsing them. parse being a monoid homomorphism would then guarantee the same results would be obtained.

Further reading[edit | edit source]

  • Additional comment on finger trees (Haskell Cafe): FingerTrees.
  • Additional comments on Monoid usage in Cabal (Haskell Cafe): [3]; [4].

Notes

  1. You will later find that two of those instances are defined in Data.Monoid already.
  2. This blog post, based on a paper by Ralf Hinze and Ross Patterson, contains a brief and accessible explanation on how monoids are used in finger trees.
  3. Sources of the quotes (Haskell Cafe mailing list): [1], [2].
  4. The snippets were taken from Ivy Foster's example config in the HaskellWiki and XMonad's XMonad.ManageHook module as of version 0.11.
  5. Source (Haskell Cafe)