Difference between revisions of "Monads as computation"

From HaskellWiki
Jump to navigation Jump to search
 
Line 1: Line 1:
  +
Programmers in general, and functional programmers in particular, are usually not so content to solve a problem in a fragile way by coding a solution directly. Quite often the best way to solve a problem is to design a domain-specific language in which the solution to one's problem is easily expressed. Doing this generally ensures that a wide class of similar problems can be attacked using the same code.
A
 
  +
  +
Better still, we'd like to embed those domain specific languages into the language which we wrote them in, so that they can be used together, and so we get benefits from the language we're working in without so much extra work. So we write combinator libraries which are essentially libraries of code whose API's are sufficiently powerful that using the library is like programming in a small language embedded within the existing one.
  +
  +
Such a library will have some primitive computations, and some ways to glue those computations together into more complex ones. A parsing library might define primitive parsers for parsing single characters, and then combining functions for concatenating parsers or selecting between them. A drawing library might define some basic drawing operations, and then various means of combining drawings into larger ones (on top, beside, above, etc.).
  +
  +
As far as programming is concerned, a monad is just a particular style of combinator library. That is, one which supports a few basic means of combination.
  +
  +
The reason for making this abstraction is so that all the libraries which make use of those means of combination can then share a library of combining functions built up from the primitive ones they are required to support.
  +
  +
Specifically, by defining an instance of Monad for your library when appropriate, you automatically get the benefit of the functions in the [http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html Control.Monad library] (as well as a few others, like [http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Traversable.html Data.Traversable]). This includes things like for-each loops (forM/mapM), ways to turn pure functions into combiners (liftM2, etc.), as well as other control structures which you get for free just for making your library an instance of Monad.
  +
  +
There are of course, other kinds of combinator library, but monads arise fairly naturally from a few basic premises.
  +
  +
* Monadic computations have results. This is reflected in the types. Given a monad M, a value of type <code>M t</code> is a computation resulting in a value of type <code>t</code>.
  +
* For any value, there is a computation which "does nothing", and produces that result. This is given by defining the function <code>return</code> for the given monad.<haskell>
  +
return :: (Monad m) => a -> m a
  +
</haskell>
  +
* Given a pair of computations <hask>x</hask> and <hask>y</hask>, one can form the computation <hask>x >> y</hask>, which intuitively "runs" the computation <hask>x</hask>, throws away its result, then runs <hask>y</hask> returning its result.<haskell>
  +
(>>) :: (Monad m) => m a -> m b -> m b
  +
</haskell>
  +
* Further, we're allowed to use the result of the first computation to decide "what to do next", rather than just throwing it away. This idea is embodied by the operation <hask>(>>=)</hask>, called 'bind'. If <hask>x</hask> is a computation, and <hask>f</hask> is a function from potential results of that computation to further computations to be performed, then <hask>x >>= f</hask> is a computation which runs <hask>x</hask>, then applies <hask>f</hask> to its result, getting a computation which it then runs. The result of this latter computation is the result of the combined one.<haskell>
  +
(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
  +
</haskell>
  +
  +
In fact, once we have bind, we can always define <hask>(>>)</hask> as:
  +
<haskell>
  +
x >> y = x >>= (\k -> y)
  +
</haskell>
  +
  +
It's important to realise that both what it means to "run" a computation, and what "then" means in the above are both <em>up to the monad in question</em> (subject to a few simple constraints to be discussed later). This point will become clearer as one sees more and more examples.
  +
  +
On top of <hask>return</hask> and <hask>(>>=)</hask>, any given monad will typically define a bunch of primitive computations to get the user of the library started. The <hask>IO</hask> monad, for instance, has a large number of I/O operations such as <hask>getLine :: IO String</hask> and <hask>putStrLn :: String -> IO ()</hask>. The program: <haskell>
  +
main :: IO ()
  +
main = getLine >>= putStrLn
  +
</haskell> gets a line of text from the user, and then prints it back out.
  +
For a slightly more complicated example, the program: <haskell>
  +
main :: IO ()
  +
main = putStrLn "Enter a line of text:"
  +
>> getLine >>= \x -> putStrLn (reverse x)
  +
</haskell> prompts the user for a line of text, gets the line of text from the user, and then prints it back out in reverse.
  +
  +
A parsing monad might define <hask>char :: Char -> Parser Char</hask>, for constructing a parser which succeeds if the input string matches the given character. As a very simple example, the parser: <haskell>
  +
cat = char 'c' >> char 'a' >> char 't'
  +
</haskell> would try to match the string "cat".
  +
  +
Because computations are typically going to be built up from long chains of <hask>(>>)</hask> and <hask>(>>=)</hask>, in Haskell, we have some syntax-sugar, called do-notation.
  +
  +
The do-notation allows us to write our second IO program above as:
  +
<haskell>
  +
main = do putStrLn "Enter a line of text:"
  +
x <- getLine
  +
putStrLn (reverse x)
  +
</haskell>
  +
  +
This gives monadic computations a bit of an imperative feel to them, but it's important to remember that the monad in question gets to decide what the combination means, and so some unusual forms of control flow might actually occur. In some monads (like parsers, or the list monad), "backtracking" may occur, and in others, even more exotic forms of control might show up.
  +
  +
The basic mechanical translation for the do-notation is as follows:
  +
<haskell>
  +
do { x } = x
  +
  +
do { x ; <stmts> }
  +
= x >> do { <stmts> }
  +
  +
do { v <- x ; <stmts> }
  +
= x >>= \v -> do { <stmts> }
  +
  +
do { let <decls> ; <stmts> }
  +
= let <decls> in do { <stmts> }
  +
</haskell>
  +
  +
TODO: Describe some examples from Control.Monad, the whole reason we bother with this in the first place. :)

Revision as of 18:46, 1 August 2007

Programmers in general, and functional programmers in particular, are usually not so content to solve a problem in a fragile way by coding a solution directly. Quite often the best way to solve a problem is to design a domain-specific language in which the solution to one's problem is easily expressed. Doing this generally ensures that a wide class of similar problems can be attacked using the same code.

Better still, we'd like to embed those domain specific languages into the language which we wrote them in, so that they can be used together, and so we get benefits from the language we're working in without so much extra work. So we write combinator libraries which are essentially libraries of code whose API's are sufficiently powerful that using the library is like programming in a small language embedded within the existing one.

Such a library will have some primitive computations, and some ways to glue those computations together into more complex ones. A parsing library might define primitive parsers for parsing single characters, and then combining functions for concatenating parsers or selecting between them. A drawing library might define some basic drawing operations, and then various means of combining drawings into larger ones (on top, beside, above, etc.).

As far as programming is concerned, a monad is just a particular style of combinator library. That is, one which supports a few basic means of combination.

The reason for making this abstraction is so that all the libraries which make use of those means of combination can then share a library of combining functions built up from the primitive ones they are required to support.

Specifically, by defining an instance of Monad for your library when appropriate, you automatically get the benefit of the functions in the Control.Monad library (as well as a few others, like Data.Traversable). This includes things like for-each loops (forM/mapM), ways to turn pure functions into combiners (liftM2, etc.), as well as other control structures which you get for free just for making your library an instance of Monad.

There are of course, other kinds of combinator library, but monads arise fairly naturally from a few basic premises.

  • Monadic computations have results. This is reflected in the types. Given a monad M, a value of type M t is a computation resulting in a value of type t.
  • For any value, there is a computation which "does nothing", and produces that result. This is given by defining the function return for the given monad.
    return :: (Monad m) => a -> m a
    
  • Given a pair of computations x and y, one can form the computation x >> y, which intuitively "runs" the computation x, throws away its result, then runs y returning its result.
    (>>) :: (Monad m) => m a -> m b -> m b
    
  • Further, we're allowed to use the result of the first computation to decide "what to do next", rather than just throwing it away. This idea is embodied by the operation (>>=), called 'bind'. If x is a computation, and f is a function from potential results of that computation to further computations to be performed, then x >>= f is a computation which runs x, then applies f to its result, getting a computation which it then runs. The result of this latter computation is the result of the combined one.
    (>>=) :: (Monad m) => m a -> (a -> m b) -> m b
    

In fact, once we have bind, we can always define (>>) as:

x >> y = x >>= (\k -> y)

It's important to realise that both what it means to "run" a computation, and what "then" means in the above are both up to the monad in question (subject to a few simple constraints to be discussed later). This point will become clearer as one sees more and more examples.

On top of return and (>>=), any given monad will typically define a bunch of primitive computations to get the user of the library started. The IO monad, for instance, has a large number of I/O operations such as getLine :: IO String and putStrLn :: String -> IO (). The program:
main :: IO ()
main = getLine >>= putStrLn
gets a line of text from the user, and then prints it back out. For a slightly more complicated example, the program:
main :: IO ()
main = putStrLn "Enter a line of text:"
         >> getLine >>= \x -> putStrLn (reverse x)
prompts the user for a line of text, gets the line of text from the user, and then prints it back out in reverse. A parsing monad might define char :: Char -> Parser Char, for constructing a parser which succeeds if the input string matches the given character. As a very simple example, the parser:
cat = char 'c' >> char 'a' >> char 't'
would try to match the string "cat".

Because computations are typically going to be built up from long chains of (>>) and (>>=), in Haskell, we have some syntax-sugar, called do-notation.

The do-notation allows us to write our second IO program above as:

main = do putStrLn "Enter a line of text:"
          x <- getLine
          putStrLn (reverse x)

This gives monadic computations a bit of an imperative feel to them, but it's important to remember that the monad in question gets to decide what the combination means, and so some unusual forms of control flow might actually occur. In some monads (like parsers, or the list monad), "backtracking" may occur, and in others, even more exotic forms of control might show up.

The basic mechanical translation for the do-notation is as follows:

do { x } = x

do { x ; <stmts> }
  = x >> do { <stmts> }

do { v <- x ; <stmts> }
  = x >>= \v -> do { <stmts> }

do { let <decls> ; <stmts> }
  = let <decls> in do { <stmts> }

TODO: Describe some examples from Control.Monad, the whole reason we bother with this in the first place. :)