
Working with monads and monad stacks
Monads are very useful abstractions, and like any sufficiently complex abstraction, many monads too incur some overhead. Two notable exceptions are IO and ST, which are eliminated during compilation. A single simple monad such as Reader or Writer has very minimal overhead, but monad stacks can incur unfortunate slowdowns. In most cases, the convenient nature of programming in a monad stack far outweighs the small overhead, because cost centers are rarely located in monad operations (excluding IO and ST).
Note
If you have an expensive subroutine in a State monad, it might be possible to convert it to ST for a big speedup. However, State
is more expressive than ST so conversion is not always feasible.
The list monad and its transformer
The monad instance of lists admits attractive backtracking. For example, consider special Pythagorean triplets from Project Euler problem 9: find three natural numbers a < b < c such that a^2 + b^2 = c^2 and a + b + c = n, where n = 1000 (there exists exactly one such triplet). A naive implementation using the list
monad can be given as follows:
-- file: backtracking-list.hs import Control.Monad (guard) special_pythagorean :: Int -> [(Int,Int,Int)] special_pythagorean n = do a <- [1 .. n] b <- [a + 1 .. n] c <- [b + 1 .. n] guard (a + b + c == n) guard (a ^ 2 + b ^ 2 == c ^ 2) return (a, b, c) main = print $ head $ special_pythagorean 1000
Algorithmically, this solution is pretty bad. But the implementation itself is fairly efficient. GHC is smart enough to optimize all intermediate lists away, producing a program with three nested loops. Most values get unboxed, too.
Previously we observed that lists don't perform well if used like lists and arrays are used in imperative languages, that is, treating them as just some list-like values. Instead, in a functional style, lists are more useful when used as a control structure. Indeed, the list monad goes by another name, the stream monad. If you ever take a look at how stream fusion in bytestring
, vector
, text
, or built-in iterators in imperative languages such as Python and Java are implemented, what you'll find is just a linked list in disguise.
The list monad can be turned into a monad transformer, named ListT
, albeit it is tricky to get right. A correct implementation can be found in the list-t
package.
With ListT
, we can add streaming to any monad. For example, we could implement a random noise generator with a repeating pattern and random delays with a ListT IO
. First, some imports:
-- file: noise.hs import ListT -- package list-t import System.Random -- package random import Control.Monad.Trans (lift) -- package mtl import Control.Concurrent (threadDelay)
We write the noise generator to take the pattern as an argument:
noise :: [Double] -> ListT IO Double noise pat = do pat'<- ListT.repeat pat x <- ListT.fromFoldable pat' lift $ do delay <- randomIO threadDelay (mod delay 300000) randomRIO (x - 0.5, x + 0.5) main = let generator = noise [1,5,10,5] in ListT.traverse_ print generator
Monadic code in ListT
looks just like monadic code in []
, with the addition of interleaved IO actions via lift
. In main
, we create a generator and consume it one element at a time. The next item is generated only when it is really required, hence we don't loop indefinitely but recurse productively.
In the list-t
package, there is a MonadPlus
instance for Monad m => ListT m
. MonadPlus
gives us the empty list (mzero
) and list concatenation (mplus
) lifted to ListT m
for any monad m
. Of course, we can also use other generic combinators, for example, to make derived generators:
Control.Monad.mfilter (> 5) (noise [1,5,10,5]) Control.Monad.liftM (+) (noise [1,2,3]) (noise [7,6,8])
However, that second example is a bit questionable, because it incurs random delays from both generators sequentially.
Free monads
Another general example of data as a control structure is the Free
monad:
data Free f a = Pure a | Free (f (Free f a))
The key observation is that if f
is a (law-abiding) functor, then Free f
is automatically always a monad.
With Free
, we can define embedded languages in Haskell quite conveniently. Let's take a silly example: a language capable of reading and writing strings, and launching missiles, that is, to perform arbitrary I/O actions. We could write an abstract datatype like so:
data Language = Write String Language | Read (String -> Language) | Missiles (IO ()) Language| End
Then, expressions could be written like so:
Write "Launch?" (Read (\s -> if s == "y" then Missiles launch End else Write "No launch" End))
But this doesn't look very nice. Certainly not nearly as readable as direct Haskell. We could roll our own parser, but fortunately there is Free
:
-- file: free.hs {-# LANGUAGE DeriveFunctor #-} import Prelude hiding (read) import Control.Monad.Free -- package free
We begin our Free
adventure with that preamble. Free
will capture the recursive nature in our Language
datatype for us when we write it as:
data Language next = Write String next | Read (String -> next) | Missiles (IO ()) next deriving (Functor) type Program = Free Language
We need DeriveFunctor
to derive the Functor
instance. Alternatively, we could have written it by hand. To lift statements in our language to the free monad Program
, we write the following definitions:
read :: Program String read = liftF (Read id) write :: String -> Program () write string = liftF (Write string ()) missiles :: IO () -> Program () missiles io = liftF (Missiles io ())
With these statements, we can write programs in monadic style in our Program
monad. The following example program repeatedly asks for a command until receiving a "launch"
command, after which it launches some missiles and exits gracefully:
program :: Program Int program = do write "Waiting for command (launch)" input <- read case input of "launch" -> do missiles $ putStrLn "Missiles launched!" return 0 _ -> do write $ "Unknown command: " ++ input program
An interpreter for this Free
language is implemented very similarly, as in the case of a direct ADT:
interpret :: Program a -> IO a interpret (Pure res) = return res interpret (Free program) = case program of Write string next -> putStrLn string >> interpret next Read go -> getLine >>= interpret . go Missiles m next -> m >> interpret next
Note that nothing prevents us from writing a safe interpreter that doesn't launch missiles, or an interpreter that doesn't live in the IO monad. Using Free
, we got monadic do-syntax for free, as well as all standard monad machinery in our little embedded language. Also, similarly to ListT
, there is a FreeT
monad transformer, with which side-effects in arbitrary inner monads can be allowed inside the embedded language.
Working with monad transformers
In general, monads from the transformers
package behave very nicely. Overhead is pretty much predicted by the number of layers in the stack. Monadic functions inline well and GHC is able to do lots of optimizations. The monad transformer library (mtl) isn't much worse nowadays, but the extra flexibility in mtl doesn't always come for free.
If you need to speed up a monad stack, you might want to consider unrolling it. The RWS monad/transformer from mtl
is an example of unrolling. RWS combines Reader, Writer, and State on a single level:
RWS r w s a ~ r -> s -> (a, s, w) ReaderT r (StateT s (Writer w)) a ~ r -> s -> ((a, s), w)
Composing monads and side-effects efficiently is ongoing research. Also, new approaches such as extensible effects have emerged, but speed remains an issue.
Speedup via continuation-passing style
Implementing monads in continuation-passing style (CPS) can have very good results. Unfortunately, no widely-used or supported library I'm aware of would provide drop-in replacements for ubiquitous Maybe, List, Reader, Writer, and State monads.
It's not that hard to implement the standard monads in CPS from scratch. For example, the State
monad can be implemented using the Cont
monad from mtl
as follows:
-- file: cont-state-writer.hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} import Control.Monad.State.Strict import Control.Monad.Cont newtype StateCPS s r a = StateCPS (Cont (s -> r) a) deriving (Functor, Applicative, Monad, MonadCont) instance MonadState s (StateCPS s r) where get = StateCPS $ cont $ \next curState → next curState curState put newState = StateCPS $ cont $ \next curState → next () newState runStateCPS :: StateCPS s s () -> s -> s runStateCPS (StateCPS m) = runCont m (\_ -> id)
In case you're not familiar with the continuation-passing style and the Cont
monad, the details might not make much sense: instead of just returning results from a function, a function in CPS applies its results to a continuation. So in short, to "get" the state in continuation-passing style, we pass the current state to the "next" continuation (first argument) and don't change the state (second argument). To "put,"we call the continuation with the unit (no return value) and change the state to a new state (second argument to next).
StateCPS
is used just like the State
monad:
action :: MonadState Int m => m () action = replicateM_ 1000000 $ do i <- get put $! i + 1 main = do print $ (runStateCPS action 0 :: Int) print $ (snd $ runState action 0 :: Int)
That action
operation is, in the CPS version of the state monad, about 5% faster and performs 30% less heap allocation than the state monad from mtl
. This program is limited pretty much only by the speed of monadic composition, so these numbers are at least very close to the maximum speedup we can have from CPSing the state monad. Speedups of the writer monad are probably near these results.
Other standard monads can be implemented similarly to StateCPS. The definitions can also be generalized to monad transformers over an arbitrary monad (a la ContT
). For extra speed, you might wish to combine many monads in a single CPS monad, similarly to what RWST does.