Difference between revisions of "The Monadic Way"

From HaskellWiki
Jump to navigation Jump to search
 
(Added output of the monadic evaluator and corrected some wikitext bugs)
Line 7: Line 7:
 
I'm a Haskell newbie trying to grasp such a difficult concept as the
 
I'm a Haskell newbie trying to grasp such a difficult concept as the
 
ones of Monad and monadic computation.
 
ones of Monad and monadic computation.
While [http://www.cs.utah.edu/~hal/htut/ "Yet Another Haskell
+
While [http://www.cs.utah.edu/~hal/htut/ "Yet Another Haskell Tutorial"]
Tutorial"] gave me a good understanding of the type system when it
+
gave me a good understanding of the type system when it
 
comes to monads I find it almost unreadable.
 
comes to monads I find it almost unreadable.
  +
 
But I had also Welder's paper, and started reading it. Well, just
 
But I had also Welder's paper, and started reading it. Well, just
 
wonderful! It explains how to ''create'' a monad!
 
wonderful! It explains how to ''create'' a monad!
  +
 
So I decided to "translate it", in order to clarify to myself the
 
So I decided to "translate it", in order to clarify to myself the
 
topic. And I'm now sharing this traslation (not completed yet) with
 
topic. And I'm now sharing this traslation (not completed yet) with
 
the hope it will be useful to someone else.
 
the hope it will be useful to someone else.
  +
 
Moreover, that's a wiki, so please improve it. And, specifically,
 
Moreover, that's a wiki, so please improve it. And, specifically,
 
correct my poor English. I'm Italian, afterall.
 
correct my poor English. I'm Italian, afterall.
Line 22: Line 25:
 
Let's start with something simple: suppose we want to implement a new
 
Let's start with something simple: suppose we want to implement a new
 
programming language. We just finished with
 
programming language. We just finished with
[http://swiss.csail.mit.edu/classes/6.001/abelson-sussman-lectures/
+
[http://swiss.csail.mit.edu/classes/6.001/abelson-sussman-lectures/ Abelson and Sussman's Structure and Interpretation of ComputerPrograms]
 
and we want to test what we have learned.
Abelson and Sussman's Structure and Interpretation of Computer
 
Programs] and we want to test what we have learned.
 
   
 
Our programming language will be very simple: it will just compute the
 
Our programming language will be very simple: it will just compute the
 
sum operation.
 
sum operation.
  +
 
So we have just one primitive operation (Add) that takes two constants
 
So we have just one primitive operation (Add) that takes two constants
 
and calculates their sum
 
and calculates their sum
  +
 
For instance, something like:
 
For instance, something like:
   
Line 68: Line 72:
 
Very very simple. The evaluator checks if its argument is a Cons: if
 
Very very simple. The evaluator checks if its argument is a Cons: if
 
it is it just returns it.
 
it is it just returns it.
  +
 
If it's not a Cons, but it is a Term, it evaluates the right one and
 
If it's not a Cons, but it is a Term, it evaluates the right one and
 
sums the result with the result of the evaluation of the second term.
 
sums the result with the result of the evaluation of the second term.
Line 77: Line 82:
 
Well, but Haskell is a pure functional language, with no side effects,
 
Well, but Haskell is a pure functional language, with no side effects,
 
we were told.
 
we were told.
  +
 
Now we seem to be wanting to create a side effect of the computation,
 
Now we seem to be wanting to create a side effect of the computation,
 
its output, and be able to stare at it...
 
its output, and be able to stare at it...
 
If we had some global variable to store the out that would be
 
If we had some global variable to store the out that would be
 
simple...
 
simple...
  +
 
But we can create the output and carry it along the computation,
 
But we can create the output and carry it along the computation,
 
concatenating it with the old one, and present it at the end of the
 
concatenating it with the old one, and present it at the end of the
 
evaluation together with the evaluation of the expression!
 
evaluation together with the evaluation of the expression!
  +
 
Simple and neat!
 
Simple and neat!
   
Line 111: Line 119:
 
is actually a pair of a variable type a (an Int in our evaluator) and
 
is actually a pair of a variable type a (an Int in our evaluator) and
 
a type Output, a string.
 
a type Output, a string.
  +
 
So our evaluator, now, will take a Term (the type of the expressions
 
So our evaluator, now, will take a Term (the type of the expressions
 
in our new programming language) and will produce a pair, composed of
 
in our new programming language) and will produce a pair, composed of
Line 116: Line 125:
   
 
So far so good. But what's happening inside the evaluator?
 
So far so good. But what's happening inside the evaluator?
  +
 
The first part will just return a pair with the number evaluated and
 
The first part will just return a pair with the number evaluated and
 
the output formatted by formatLine.
 
the output formatted by formatLine.
  +
 
The second part does something more complicated: it returns a pair
 
The second part does something more complicated: it returns a pair
 
composed by
 
composed by
Line 152: Line 163:
 
sum, together with the output coming from their calculation (to be
 
sum, together with the output coming from their calculation (to be
 
concatenated by the expression x ++ y ++ formatLine ...).
 
concatenated by the expression x ++ y ++ formatLine ...).
  +
 
So we need to separate the pairs produced by "evalO t" and "eval u"
 
So we need to separate the pairs produced by "evalO t" and "eval u"
 
(remember: eval now produces a value of type M Int, i.e. a pair of an
 
(remember: eval now produces a value of type M Int, i.e. a pair of an
Line 162: Line 174:
 
Let's analyze the evaluator from another perspective. From the type
 
Let's analyze the evaluator from another perspective. From the type
 
perspective.
 
perspective.
  +
 
We solved our problem by creating a new type, a pair of an Int (the
 
We solved our problem by creating a new type, a pair of an Int (the
 
result of the evaluation) and a String (the output of the process of
 
result of the evaluation) and a String (the output of the process of
Line 175: Line 188:
 
Let's focus on the "stores" action. The correct term should be
 
Let's focus on the "stores" action. The correct term should be
 
"binds".
 
"binds".
  +
 
Take a function:
 
Take a function:
 
<haskell>
 
<haskell>
Line 181: Line 195:
 
"x" appears on both sides of the expression. We say that on the right
 
"x" appears on both sides of the expression. We say that on the right
 
side "x" is bound to the value of x given on the left side.
 
side "x" is bound to the value of x given on the left side.
  +
 
So
 
So
 
<haskell>
 
<haskell>
Line 186: Line 201:
 
</haskell>
 
</haskell>
 
binds x to 3 for the evaluation of the expression "x + x".
 
binds x to 3 for the evaluation of the expression "x + x".
  +
 
Our evaluator binds "a" and "x" / "b" and "y" with the evaluation of
 
Our evaluator binds "a" and "x" / "b" and "y" with the evaluation of
 
"eval t" and "eval u" respectively. "a","b","x" and "y" will be then
 
"eval t" and "eval u" respectively. "a","b","x" and "y" will be then
 
used in the evaluation of ((a+)(x ++ ...).
 
used in the evaluation of ((a+)(x ++ ...).
  +
 
We know that there is an ad hoc operator for binding variables to a
 
We know that there is an ad hoc operator for binding variables to a
 
value: lambda, or \.
 
value: lambda, or \.
  +
 
Indeed f x = x + x is syntactic sugar for:
 
Indeed f x = x + x is syntactic sugar for:
 
<haskell>
 
<haskell>
Line 199: Line 217:
   
 
So we can try to abstract this phenomenon.
 
So we can try to abstract this phenomenon.
  +
 
What we need is a function that takes our composed type MOut Int and a
 
What we need is a function that takes our composed type MOut Int and a
 
function in order to produce a new MOut Int, concatenating the
 
function in order to produce a new MOut Int, concatenating the
 
output of the computation of the first with the output of the
 
output of the computation of the first with the output of the
 
computation of the second.
 
computation of the second.
  +
 
This is what bindM does:
 
This is what bindM does:
   
Line 215: Line 235:
   
 
It takes:
 
It takes:
1. "m": the compound type MOut Int carrying the result of an "eval
+
* "m": the compound type MOut Int carrying the result of an "eval
 
Term",
 
Term",
2. a function "f". This function will take the Int ("a") extracted by the
+
* a function "f". This function will take the Int ("a") extracted by the
 
evaluation of "m" ((a,x)=m). This function will produce anew pair: a
 
evaluation of "m" ((a,x)=m). This function will produce anew pair: a
 
new Int produced by a new evaluation; some new output.
 
new Int produced by a new evaluation; some new output.
  +
 
bindM will return the new Int in pair with the concatenated outputs
 
bindM will return the new Int in pair with the concatenated outputs
 
resulting from the evaluation of "m" and "f a".
 
resulting from the evaluation of "m" and "f a".
Line 240: Line 261:
   
 
Let's start from the outside:
 
Let's start from the outside:
  +
  +
</haskell>
 
bindM (evalM_1 u) (\b -> ((a + b), formatLine (Add t u) (a + b)))
 
bindM (evalM_1 u) (\b -> ((a + b), formatLine (Add t u) (a + b)))
  +
</haskell>
   
 
bindM takes the result of the evaluation "evalM_1 u", a type Mout Int,
 
bindM takes the result of the evaluation "evalM_1 u", a type Mout Int,
 
and a function. It will extract the Int from that type and use it to
 
and a function. It will extract the Int from that type and use it to
 
bind "b".
 
bind "b".
  +
 
So in bindM (evalM_1 u)... "b" will be bound to a value.
 
So in bindM (evalM_1 u)... "b" will be bound to a value.
   
Line 273: Line 298:
   
 
First we need a method for creating someting of type M a, starting from
 
First we need a method for creating someting of type M a, starting from
something of type a. This is what evalM_2 (Con a) is doing, after all.
+
something of type a. This is what <hask>evalM_2 (Con a)</hask> is doing, after all.
 
Very simply:
 
Very simply:
   
Line 311: Line 336:
   
 
Well, this is fine, definetly better then before, anyway.
 
Well, this is fine, definetly better then before, anyway.
  +
 
Still we use `bindM` \_ -> that binds something we do not use (_). We
 
Still we use `bindM` \_ -> that binds something we do not use (_). We
 
could write something for this case, when we concatenate computations
 
could write something for this case, when we concatenate computations
Line 370: Line 396:
 
Now our evaluator has been completely transformed into a monadic
 
Now our evaluator has been completely transformed into a monadic
 
evaluator. That's what it is: a monad.
 
evaluator. That's what it is: a monad.
  +
 
We have a function that constructs an object of type MO Int, formed by
 
We have a function that constructs an object of type MO Int, formed by
 
a pair: the result of the evaluation and the accumulated
 
a pair: the result of the evaluation and the accumulated
 
(concatenated) output.
 
(concatenated) output.
  +
 
The process of accumulation and the act of parting the MO Int into its
 
The process of accumulation and the act of parting the MO Int into its
 
component is buried into bindM, that can also preserve some value for
 
component is buried into bindM, that can also preserve some value for
 
later uses.
 
later uses.
  +
 
So we have:
 
So we have:
MO a type constructor for a type carrying a pair composed by an Int
+
* MO a type constructor for a type carrying a pair composed by an Int
 
and a String;
 
and a String;
bindMO, that gives a direction to the process of evaluation: it
+
* bindMO, that gives a direction to the process of evaluation: it
 
concatenates computations and captures some side effects we created.
 
concatenates computations and captures some side effects we created.
mkOM lets us create an object of type MO Int starting from an Int.
+
* mkOM lets us create an object of type MO Int starting from an Int.
   
 
As you see this is all we need to create a monad. In other words
 
As you see this is all we need to create a monad. In other words
Line 387: Line 416:
 
sugar.
 
sugar.
   
So, let's have a look to that sugar: the famous do-notation!
+
So, let's have a look to that sugar: the famous do-notation!
  +
  +
We will now rewrite our basic evaluator to use it with the
  +
do-notation.
   
 
Now we have to crate a new type: this is necessary in order to use
 
Now we have to crate a new type: this is necessary in order to use
Line 446: Line 478:
 
Output, will get filled up with the concatenated output of the
 
Output, will get filled up with the concatenated output of the
 
computation.
 
computation.
  +
 
The sequencing done by bindMO (now >>=) will take care of passing to
 
The sequencing done by bindMO (now >>=) will take care of passing to
 
the next evaluation the needed Int and will do some more side
 
the next evaluation the needed Int and will do some more side
Line 458: Line 491:
 
We are creating side-effects and propagating them within our monads.
 
We are creating side-effects and propagating them within our monads.
   
Ok. Let's translate out evaluator in monadic notation:
+
Ok. Let's translate our output-producing evaluator in monadic
  +
notation:
   
 
<haskell>
 
<haskell>
Line 483: Line 517:
   
 
</haskell>
 
</haskell>
  +
  +
Let's see the evaluator with output in action:
  +
*MyMonads> eval_IO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con
  +
12))))
  +
Eval_IO (54,"eval (Con 6) <= 6 - eval (Con 16) <= 16 - eval (Con 20) <= 20 - eval (Con 12) <= 12 - eval (Add (Con 20) (Con 12)) <= 32 - eval (Add (Con 16) (Add (Con 20) (Con 12))) <= 48 - eval (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) <= 54 - ")
  +
*MyMonads>
   
  +
Let's format the output part:
  +
eval (Con 6) <= 6
  +
eval (Con 16) <= 16
  +
eval (Con 20) <= 20
  +
eval (Con 12) <= 12
  +
eval (Add (Con 20) (Con 12)) <= 32
  +
eval (Add (Con 16) (Add (Con 20) (Con 12))) <= 48
  +
eval (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) <= 54
   
 
That's it. For today...
 
That's it. For today...

Revision as of 12:31, 25 August 2006

An evaluation of Philip Wadler's "Monads for functional programming"

This tutorial is a "translation" of Philip Welder's "Monads for functional programming". (avail. from here)

I'm a Haskell newbie trying to grasp such a difficult concept as the ones of Monad and monadic computation. While "Yet Another Haskell Tutorial" gave me a good understanding of the type system when it comes to monads I find it almost unreadable.

But I had also Welder's paper, and started reading it. Well, just wonderful! It explains how to create a monad!

So I decided to "translate it", in order to clarify to myself the topic. And I'm now sharing this traslation (not completed yet) with the hope it will be useful to someone else.

Moreover, that's a wiki, so please improve it. And, specifically, correct my poor English. I'm Italian, afterall.

A Simple Evaluator

Let's start with something simple: suppose we want to implement a new programming language. We just finished with Abelson and Sussman's Structure and Interpretation of ComputerPrograms and we want to test what we have learned.

Our programming language will be very simple: it will just compute the sum operation.

So we have just one primitive operation (Add) that takes two constants and calculates their sum

For instance, something like:

 (Add (Con 5) (Con 6))

should yeld:

 11

We will implement our language with the help of a data type constructor such as:

module MyMonads where
data Term = Con Int
         | Add Term Term
           deriving (Show)

After that we build our interpreter:

eval :: Term -> Int
eval (Con a) = a
eval (Add a b) = eval a + eval b

That's it. Just an example:

 *MyMonads> eval (Add (Con 5) (Con 6))
 11
 *MyMonads>

Very very simple. The evaluator checks if its argument is a Cons: if it is it just returns it.

If it's not a Cons, but it is a Term, it evaluates the right one and sums the result with the result of the evaluation of the second term.

Some Output, Please!

Now, that's fine, but we'd like to add some features, like providing some output, to show how the computation was carried out. Well, but Haskell is a pure functional language, with no side effects, we were told.

Now we seem to be wanting to create a side effect of the computation, its output, and be able to stare at it... If we had some global variable to store the out that would be simple...

But we can create the output and carry it along the computation, concatenating it with the old one, and present it at the end of the evaluation together with the evaluation of the expression!

Simple and neat!

type MOut a = (a, Output)
type Output = String

formatLine :: Term -> Int -> Output
formatLine t a = "eval (" ++ show t ++ ") <= " ++ show a ++ " - "                                                       

evalO :: Term -> MOut Int
evalO (Con a) = (a, formatLine (Con a) a)
evalO (Add t u) = ((a + b),(x ++ y ++ formatLine (Add t u) (a + b)))
    where (a, x) = evalO t
          (b, y) = evalO u

Now we have what we want. But we had to change our evaluator quite a bit. First we added a function, that takes a Term (of the expression to be evaluated), an Int (the result of the evaluation) and gives back an output of type Output (that is a synonymous of String).

The evaluator changed quite a lot! Now it has a different type: it takes a Term data type and produces a new type, we called MOut, that is actually a pair of a variable type a (an Int in our evaluator) and a type Output, a string.

So our evaluator, now, will take a Term (the type of the expressions in our new programming language) and will produce a pair, composed of the result of the evaluation (an Int) and the Output, a string.

So far so good. But what's happening inside the evaluator?

The first part will just return a pair with the number evaluated and the output formatted by formatLine.

The second part does something more complicated: it returns a pair composed by 1. the result of the evaluation of the right Term summed to the result of the evaluation of the second Term 2. the output: the concatenation of the output produced by the evaluation of the right Term, the output produced by the evaluation of the left Term (each this evaluation returns a pair with the number and the output), and the formatted output of the evaluation.

Let's try it:

 *MyMonads> evalO (Add (Con 5) (Con 6))
 (11,"eval (Con 5) <= 5 - eval (Con 6) <= 6 - eval (Add (Con 5) (Con 6)) <= 11 - ")
 *MyMonads>

It works! Let's put the output this way:

 eval (Con 5) <= 5 - 
 eval (Con 6) <= 6 - 
 eval (Add (Con 5) (Con 6)) <= 11 -

Great! We are able to produce a side effect of our evaluation and present it at the end of the computation, after all.

Let's have a closer look at this expression:

evalO (Add t u) = ((a + b),(x ++ y ++ formatLine (Add t u) (a + b)))
     where (a, x) = evalO t
           (b, y) = evalO u

Why all that? The problem is that we need "a" and "b" to calculate their sum, together with the output coming from their calculation (to be concatenated by the expression x ++ y ++ formatLine ...).

So we need to separate the pairs produced by "evalO t" and "eval u" (remember: eval now produces a value of type M Int, i.e. a pair of an Int and a String!).

Let's Go Monadic

Is there a more general way of doing so?

Let's analyze the evaluator from another perspective. From the type perspective.

We solved our problem by creating a new type, a pair of an Int (the result of the evaluation) and a String (the output of the process of evaluation).

The first part of the evaluator does nothing else but creating, from a value of type Int, an object of type M Int (Int,Output). It does so by creating a pair with that Int and some text.

The second part evaluates the two Term(s) and "stores" the values thus produced in some variables to be use later to compute the output.

Let's focus on the "stores" action. The correct term should be "binds".

Take a function:

f x = x + x

"x" appears on both sides of the expression. We say that on the right side "x" is bound to the value of x given on the left side.

So

f 3

binds x to 3 for the evaluation of the expression "x + x".

Our evaluator binds "a" and "x" / "b" and "y" with the evaluation of "eval t" and "eval u" respectively. "a","b","x" and "y" will be then used in the evaluation of ((a+)(x ++ ...).

We know that there is an ad hoc operator for binding variables to a value: lambda, or \.

Indeed f x = x + x is syntactic sugar for:

f = \x -> x + x

When we write f 3 we are actually binding "x" to 3 within what's next "->", that will be used (substituted) for evaluating f 3.

So we can try to abstract this phenomenon.

What we need is a function that takes our composed type MOut Int and a function in order to produce a new MOut Int, concatenating the output of the computation of the first with the output of the computation of the second.

This is what bindM does:

bindM :: MOut a -> (a -> MOut b) -> MOut b
bindM m f = (b, x ++ y)
            where (a, x) = m
                  (b, y) = f a

It takes:

  • "m": the compound type MOut Int carrying the result of an "eval

Term",

  • a function "f". This function will take the Int ("a") extracted by the

evaluation of "m" ((a,x)=m). This function will produce anew pair: a new Int produced by a new evaluation; some new output.

bindM will return the new Int in pair with the concatenated outputs resulting from the evaluation of "m" and "f a".

So let's write the new version of the evaluator:

evalM_1 :: Term -> MOut Int
evalM_1 (Con a) = (a, formatLine (Con a) a)
evalM_1 (Add t u) = bindM (evalM_1 t) (\a -> 
                                     bindM (evalM_1 u) (\b -> 
                                                        ((a + b), formatLine (Add t u) (a + b))
                                                    )
                                    )

Ugly, isn't it?

Let's start from the outside:

</haskell> bindM (evalM_1 u) (\b -> ((a + b), formatLine (Add t u) (a + b))) </haskell>

bindM takes the result of the evaluation "evalM_1 u", a type Mout Int, and a function. It will extract the Int from that type and use it to bind "b".

So in bindM (evalM_1 u)... "b" will be bound to a value.

Then the outer part (bindM (evalM_1 t) (\a...) will bind "a" to the value needed to evaluate "((a+b), formatLine...) and produce our final MOut Int.

We can write the evaluator in a more convinient way, now that we know what it does:

evalM_2 :: Term -> MOut Int
evalM_2 (Con a) = (a, formatLine (Con a) a)
evalM_2 (Add t u) = evalM_2 t `bindM` \a ->
                    evalM_2 u `bindM` \b ->
                    ((a + b), (formatLine (Add t u) (a + b)))

Now, look at the first part:

evalM_2 (Con a) = (a, formatLine (Con a) a)

We could use a more general way of creating some output.

First we need a method for creating someting of type M a, starting from something of type a. This is what evalM_2 (Con a) is doing, after all. Very simply:

mkM :: a -> MOut a
mkM a = (a, "")

We then need to "insert" some text (Output) in our type M:

outPut :: Output -> MOut ()
outPut x = ((), x)

Very simple: we have a string "x" (Output) and create a pair with a () instead of an Int, and the output.

This way we will be able to define also this firts part in terms of bindM, that will take care of concatenating outputs.

So we have now a new evaluator:

evalM_3 :: Term -> MOut Int
evalM_3 (Con a) = outPut (formatLine (Con a) a) `bindM` \_ -> mkM a
evalM_3 (Add t u) = evalM_3 t `bindM` \a ->
                   evalM_3 u `bindM` \b ->
                   outPut (formatLine (Add t u) (a + b)) `bindM` \_ -> mkM (a + b)

Well, this is fine, definetly better then before, anyway.

Still we use `bindM` \_ -> that binds something we do not use (_). We could write something for this case, when we concatenate computations without the need of binding variables. Let's call it `combineM`:

combineM :: MOut a -> MOut b -> MOut b
combineM m f = m `bindM` \_ -> f

So the new evaluator:

evalM :: Term -> MOut Int
evalM (Con a) = outPut (formatLine (Con a) a) `combineM` 
                mkM a
evalM (Add t u) = evalM t `bindM` \a ->
                  evalM u `bindM` \b ->
                  outPut (formatLine (Add t u) (a + b)) `combineM` 
                  mkM (a + b)

Let's put everything together (and change some names):

type MO a = (a, Out)
type Out = String

mkMO :: a -> MO a
mkMO a = (a, "")

bindMO :: MO a -> (a -> MO b) -> MO b
bindMO m f = (b, x ++ y)
             where (a, x) = m
                   (b, y) = f a

combineMO :: MO a -> MO b -> MO b
combineMO m f = m `bindM` \_ -> f

outMO :: Out -> MO ()
outMO x = ((), x)
 
evalMO :: Term -> MO Int
evalMO (Con a) = outMO (formatLine (Con a) a) `combineMO`
                 mkMO a
evalMO (Add t u) = evalMO t `bindMO` \a ->
                   evalMO u `bindMO` \b ->
                   outMO (formatLine (Add t u) (a + b)) `combineMO` 
                   mkMO (a + b)

Some Sugar, Please!

Now our evaluator has been completely transformed into a monadic evaluator. That's what it is: a monad.

We have a function that constructs an object of type MO Int, formed by a pair: the result of the evaluation and the accumulated (concatenated) output.

The process of accumulation and the act of parting the MO Int into its component is buried into bindM, that can also preserve some value for later uses.

So we have:

  • MO a type constructor for a type carrying a pair composed by an Int

and a String;

  • bindMO, that gives a direction to the process of evaluation: it

concatenates computations and captures some side effects we created.

  • mkOM lets us create an object of type MO Int starting from an Int.

As you see this is all we need to create a monad. In other words monads arise from the type system. Everything else is just syntactic sugar.

So, let's have a look to that sugar: the famous do-notation!

We will now rewrite our basic evaluator to use it with the do-notation.

Now we have to crate a new type: this is necessary in order to use specific monadic notation and have at our disposal the more practical do-notation.

  
newtype Eval a = Eval a
    deriving (Show)

So, our type will be an instance of the monad class. We will have to define the methods of this class (>>= and return), but that will be easy since we already done that while defining bindMO and mkMO.

instance Monad Eval where
    return a = Eval a
    Eval m >>= f = f m

And then we will take the old version of our evaluator and substitute `bindMO` with >>= and `mkMO` with return:

evalM_4 :: Term -> Eval Int
evalM_4 (Con a) = return a
evalM_4 (Add t u) = evalM_4 t >>= \a ->
                    evalM_4 u >>= \b ->
                    return (a + b)

which is, in the do-notation:

evalM_5 :: Term -> Eval Int
evalM_5 (Con a) = return a
evalM_5 (Add t u) = do a <- evalM_5 t
                       b <- evalM_5 u
                       return (a + b)

Simple: do binds the result of "eval_M5 t" to a, binds the result of "eval_M5 u" to b and then returns the sum. In a very imperative style.

We can now have an image of our monad: it is out type (Eval) that is made up of a pair: during evaluation the first member of the pair (the Int) will get the results of our computation (i.e.: the procedures to calculate the final result). The second part, the String called Output, will get filled up with the concatenated output of the computation.

The sequencing done by bindMO (now >>=) will take care of passing to the next evaluation the needed Int and will do some more side calculation to produce the output (concatenating outputs resulting from computation of the new Int, for instance).

So we can grasp the basic concept of a monad: it is like a label which we attach to each step of the evaluation (the String attached to the Int). This label is persistent within the process of computation and at each step bindMO can do some manipulation of it. We are creating side-effects and propagating them within our monads.

Ok. Let's translate our output-producing evaluator in monadic notation:

newtype Eval_IO a = Eval_IO (a, O)
    deriving (Show)
type O = String

instance Monad Eval_IO where
    return a = Eval_IO (a, "")
    (>>=) m f = Eval_IO (b, x ++ y)
                       where Eval_IO (a, x) = m
                             Eval_IO (b, y) = f a
print_IO :: O -> Eval_IO ()
print_IO x = Eval_IO ((), x)
 
eval_IO :: Term -> Eval_IO Int
eval_IO (Con a) = do print_IO (formatLine (Con a) a)
                     return a
eval_IO (Add t u) = do a <- eval_IO t
                       b <- eval_IO u
                       print_IO (formatLine (Add t u) (a + b))
                       return (a + b)

Let's see the evaluator with output in action:

 *MyMonads> eval_IO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con

12))))

  Eval_IO (54,"eval (Con 6) <= 6 - eval (Con 16) <= 16 - eval (Con 20) <= 20 - eval (Con 12) <= 12 - eval (Add (Con 20) (Con 12)) <= 32 - eval (Add (Con 16) (Add (Con 20) (Con 12))) <= 48 - eval (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) <= 54 - ")
 *MyMonads> 

Let's format the output part:

 eval (Con 6) <= 6 
 eval (Con 16) <= 16 
 eval (Con 20) <= 20 
 eval (Con 12) <= 12 
 eval (Add (Con 20) (Con 12)) <= 32 
 eval (Add (Con 16) (Add (Con 20) (Con 12))) <= 48 
 eval (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) <= 54 

That's it. For today...

(TO BE CONTINUED)

Andrea Rossato arossato AT istitutocolli.org