|
|
(14 intermediate revisions by 3 users not shown) |
Line 1: |
Line 1: |
| ==An evaluation of Philip Wadler's "Monads for functional programming"==
| | '''Note''' Since the size of the previous file was getting too big for a wiki, the tutorial has been divided into two parts: [[The Monadic Way Part I]] and [[The Monadic Way Part II]]. See below for some introductory remarks. |
|
| |
|
| This tutorial is a "translation" of Philip Wedler's "Monads for
| | '''Contents''' |
| functional programming".
| |
| (avail. from [http://homepages.inf.ed.ac.uk/wadler/topics/monads.html here])
| |
|
| |
|
| I'm a Haskell newbie trying to grasp such a difficult concept as the
| | ;[[Meet Bob The Monadic Lover]] |
| ones of Monad and monadic computation.
| | :A (supposed-to-be) funny and short introduction to Monads, with code but without any reference to category theory: what monads look like and what they are useful for, from the perspective of a ... lover. It could be an introduction to "The Monadic Way" tutorial. |
| While [http://www.cs.utah.edu/~hal/htut/ "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 Wedler's paper, and started reading it. Well, just
| | ;[[The Monadic Way/Part I]] |
| wonderful! It explains how to ''create'' a monad!
| | :In the first part of the tutorial we will start from a very simple evaluator that will be transformed into a monadic evaluator with an increasing number of features: output, exceptions, and state: a very simple counter for tracking the number of recursions of the evaluation precess. |
|
| |
|
| So I decided to "translate it", in order to clarify to myself the
| | ;[[The Monadic Way/Part II]] |
| topic. And I'm now sharing this traslation (not completed yet) with
| | :In the second part of the tutorial we will see how to take complexity out of our monadic evaluator with the use of monadic transformers, and specifically StateT. This part is just a skeleton, since, for the time being, it contains only the code. |
| 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, after all.
| |
|
| |
|
| '''Note: The source of this page can be used as a Literate Haskel
| | ==Preliminary remarks== |
| file and can be run with ghci or hugs: so cut paste change'n run (in
| |
| emacs for instance) while reading it...'''
| |
|
| |
|
| ==A Simple Evaluator== | | When I started writing this tutorial I though that the only way to |
| | explain monads to a newcomer was to show them from the inside, with |
| | the use of lambda abstraction. Not only because this is the way Philip |
| | Wedler's |
| | [http://homepages.inf.ed.ac.uk/wadler/papers/marktoberdorf/baastad.pdf paper] |
| | adopts, but also because I believed, and still believe, that the |
| | only way to understand what bind (>>=) does is to explain it as a |
| | function that takes a monad and an anonymous function. |
|
| |
|
| Let's start with something simple: suppose we want to implement a new
| | I had this feeling because I am a newcomer, and this is the way I came to understand monads. |
| programming language. We just finished with
| |
| [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.
| |
| | |
| 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:
| |
| | |
| ===The basic evaluator===
| |
| <haskell>
| |
| | |
| > module TheMonadicWay where
| |
| > data Term = Con Int
| |
| > | Add Term Term
| |
| > deriving (Show)
| |
| | |
| </haskell>
| |
| | |
| After that we build our interpreter:
| |
| | |
| <haskell>
| |
| | |
| > eval :: Term -> Int
| |
| > eval (Con a) = a
| |
| > eval (Add a b) = eval a + eval b
| |
| | |
| </haskell>
| |
| | |
| That's it. Just an example:
| |
| | |
| *TheMonadicWay> eval (Add (Con 5) (Con 6))
| |
| 11
| |
| *TheMonadicWay>
| |
| | |
| Very very simple. The evaluator checks if its argument is a Con: 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!
| |
| | |
| ===The basic evaluator with output===
| |
| Simple and neat!
| |
| | |
| <haskell>
| |
| | |
| > 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
| |
| | |
| </haskell>
| |
| | |
| 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:
| |
| *TheMonadicWay> evalO (Add (Con 5) (Con 6))
| |
| (11,"eval (Con 5) <= 5 - eval (Con 6) <= 6 - eval (Add (Con 5) (Con 6)) <= 11 - ")
| |
| *TheMonadicWay>
| |
| | |
| 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:
| |
| <haskell>
| |
| | |
| evalO (Add t u) = ((a + b),(x ++ y ++ formatLine (Add t u) (a + b)))
| |
| where (a, x) = evalO t
| |
| (b, y) = evalO u
| |
| | |
| </haskell>
| |
| | |
| 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:
| |
| <haskell>
| |
| f x = x + x
| |
| </haskell>
| |
| "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
| |
| <haskell>
| |
| f 3
| |
| </haskell>
| |
| 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:
| |
| <haskell>
| |
| f = \x -> x + x
| |
| </haskell>
| |
| 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.
| |
| | |
| ===Monadic evaluator with output===
| |
| 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:
| |
| | |
| <haskell>
| |
| | |
| > bindM :: MOut a -> (a -> MOut b) -> MOut b
| |
| > bindM m f = (b, x ++ y)
| |
| > where (a, x) = m
| |
| > (b, y) = f a
| |
| | |
| </haskell>
| |
| | |
| 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:
| |
| | |
| <haskell>
| |
| | |
| > 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))
| |
| > )
| |
| > )
| |
| | |
| </haskell>
| |
| | |
| 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:
| |
| | |
| <haskell>
| |
| | |
| > 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)))
| |
| | |
| </haskell>
| |
| | |
| Now, look at the first part:
| |
| | |
| <haskell>
| |
| evalM_2 (Con a) = (a, formatLine (Con a) a)
| |
| </haskell>
| |
| | |
| 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 <hask>evalM_2 (Con a)</hask> is doing, after all.
| |
| Very simply:
| |
| | |
| <haskell>
| |
| | |
| > mkM :: a -> MOut a
| |
| > mkM a = (a, "")
| |
| | |
| </haskell>
| |
| | |
| We then need to "insert" some text (Output) in our type M:
| |
| | |
| <haskell>
| |
| | |
| > outPut :: Output -> MOut ()
| |
| > outPut x = ((), x)
| |
| | |
| </haskell>
| |
| | |
| 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:
| |
| | |
| <haskell>
| |
| | |
| > 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)
| |
| | |
| </haskell>
| |
| | |
| 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`:
| |
| | |
| <haskell>
| |
| | |
| > combineM :: MOut a -> MOut b -> MOut b
| |
| > combineM m f = m `bindM` \_ -> f
| |
| | |
| </haskell>
| |
| | |
| So the new evaluator:
| |
| | |
| <haskell>
| |
| | |
| > 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)
| |
| | |
| </haskell>
| |
| | |
| Let's put everything together (and change some names):
| |
| | |
| <haskell>
| |
| | |
| > 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)
| |
| | |
| </haskell>
| |
| | |
| ==What Does Bind Bind?==
| |
| | |
| The evaluator looks like:
| |
| <haskell>
| |
| evalM t >>= \a -> evalM u >>= \b -> outPut "something" >>= \_ -> mkM (a +b)
| |
| </haskell>
| |
| where >>= is bindM, obviously.
| |
| | |
| Let's do some substitution where
| |
| * evalM t = (a,Out)
| |
| * evalM u = (b,Out)
| |
| * outMO "string" = ((),Out)
| |
| * mkMO (a+b) = ((a+b),Out)
| |
|
| |
|
| | I did not received very much feedback for this tutorial, and I must |
| | admit that I would like to. But one person, on the haskell-cafe |
| | mailing list, [http://www.haskell.org/pipermail/haskell-cafe/2006-September/017740.html told me] |
| | that: |
| <pre> | | <pre> |
| | (a,Out) >>= \a -> (b,Out) >>= \b -> ((),Out) >>= \_ >>= ((a + b), Out)
| | imho your tutorial makes the error that is a very typical: when you |
| d | V V V V V V V V ^ ^ ^ ^
| | write your tutorial you already know what are monads and what the |
| o | |__|________^ | | ^ | | | | | |
| | program you will construct at the end. but your reader don't know all these! |
| B | |__(++)__|_Out_|__|__(++)__V_____|___|__Out___|_(++)__|___|____|
| | for such fresh reader this looks as you made some strange steps, write |
| i | | |______(b)__|_____|_____(b)____|__(b)__|___|
| | some ugly code and he doesn't have chances to understand that this ugly |
| n | |_________(a)___________|____________|__(a)__|
| | code is written just to show that this can be simplified by using monads. |
| d | |_____()_____|
| |
| | |
| </pre> | | </pre> |
|
| |
|
| Clear, isn't it?
| | I believe that Bulat is right. In this tutorial you go through some |
| | | code that is '''really''' ugly and then, with some kind of magic, it |
| "bindM" is just a function that takes care of gluing together, inside
| | turns out in the (redundant but) clean evaluator of the end of [[The Monadic Way/Part II]]. |
| a data type, a sequence of computations!
| |
| | |
| == 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:
| | I took that mail as a challenge and |
| * MO a type constructor for a type carrying a pair composed by an Int and a String;
| | [http://www.haskell.org/pipermail/haskell-cafe/2006-September/017778.html I responded] |
| * bindMO, that gives a direction to the process of evaluation: it concatenates computations and captures some side effects we created.
| | by writing [[Meet Bob The Monadic Lover]]. |
| * 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
| | In "Meet Bob" the code is clean, variable names are very descriptive, |
| monads arise from the type system. Everything else is just syntactic
| | and you see that I can create a monad without any use of lambda |
| sugar.
| | abstraction. |
|
| |
|
| So, let's have a look to that sugar: the famous do-notation!
| | Bind (in "Meet Bob" is askLover) now takes a monad and a partial |
| | application, not an anonymous function. |
|
| |
|
| ===Basic monadic evaluator in do-notation===
| | Obviously you can see an anonymous function as a partial application. |
|
| |
|
| We will now rewrite our basic evaluator to use it with the
| | The problem, I think, is that, in "Meet Bob", you cannot understand |
| do-notation. | | the strict relation between what I did before and what I do when I |
| | start using the "do-notation". You see that the same functions are |
| | being used ("tellMyself" and "newLove"), but "andrea <- tellMyself 1" |
| | is not explained. It's just magic. |
|
| |
|
| Now we have to crate a new type: this is necessary in order to use
| | The fact is that you cannot understand "andrea <- tellMyself 1" |
| specific monadic notation and have at our disposal the more practical
| | without the use of lambda abstraction. |
| do-notation.
| |
|
| |
|
| | I should have written an intermediate step, something like this: |
| <haskell> | | <haskell> |
|
| | drunk = do newLove "Paula " >> |
| > newtype Eval a = Eval a
| | (tellLover 1 10) >>= \paula -> |
| > deriving (Show) | | (tellMyself 3) >>= \lorena -> tellMyself (paula + lorena) |
| | |
| </haskell>
| |
| | |
| 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.
| |
| | |
| <haskell>
| |
| | |
| > instance Monad Eval where
| |
| > return a = Eval a | |
| > Eval m >>= f = f m
| |
| | |
| </haskell>
| |
| | |
| And then we will take the old version of our evaluator and substitute
| |
| `bindMO` with >>= and `mkMO` with return:
| |
|
| |
| <haskell>
| |
| | |
| > 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)
| |
|
| |
|
| </haskell> | | </haskell> |
|
| |
|
| which is, in the do-notation:
| | With this approach I think you can understand '''why and how''' you |
| | | come to write something like this: |
| <haskell> | | <haskell> |
| | | drunk = do newLove "Paula " |
| > evalM_5 :: Term -> Eval Int
| | paula <- (tellLover 1 10) |
| > evalM_5 (Con a) = return a
| | lorena <- tellMyself 3 |
| > evalM_5 (Add t u) = do a <- evalM_5 t
| | tellMyself (paula + lorena) |
| > b <- evalM_5 u
| |
| > return (a + b)
| |
| | |
| </haskell> | | </haskell> |
|
| |
|
| Simple: do binds the result of "eval_M5 t" to a, binds the result of
| | That is to say, in this way you can see a do block as a series of |
| "eval_M5 u" to b and then returns the sum. In a very imperative style. | | nested anonymous functions whose arguments are bound to some value by |
| | the application of >>=. Anonymous functions that bind to some value |
| | the variables appearing after the "->" ("paula" and "lorena"). |
|
| |
|
| We can now have an image of our monad: it is out type (Eval) that is
| | To summarize, I think that even if you can start using monads without |
| made up of a pair: during evaluation the first member of the pair (the
| | understanding that what happens inside a "do" block is strictly |
| Int) will get the results of our computation (i.e.: the procedures to
| | related with lambda calculus, I don't think you can claim you |
| calculate the final result). The second part, the String called
| | understand monads just because you are using them. |
| Output, will get filled up with the concatenated output of the
| |
| computation.
| |
|
| |
|
| The sequencing done by bindMO (now >>=) will take care of passing to
| | And I'm quite sure that if a problem arises somewhere you can have a |
| the next evaluation the needed Int and will do some more side
| | very difficult time in trying to find out what the problem is. This is |
| calculation to produce the output (concatenating outputs resulting
| | even more true when you start doing monadic transformations. |
| from computation of the new Int, for instance).
| |
|
| |
|
| So we can grasp the basic concept of a monad: it is like a label which
| | ==How to explain monads to newcomers?== |
| 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.
| |
|
| |
|
| ===Monadic evaluator with output in do-notation===
| | Monads are not an impossible-to-understand-unless-you-have-a-phd |
| | topic. I don't know if I can claim I'm a living proof of this |
| | assumption, since I have a PhD. But please take into account that I |
| | have a PhD in Comparative Private Law! Nothing related to computer |
| | science. And I claim I understand monads. |
|
| |
|
| Ok. Let's translate our output-producing evaluator in monadic
| | Moreover, since I have come to understand them, I think I can try to |
| notation:
| | explain them to newcomers like me. This is why I started writing this |
| | tutorial. |
|
| |
|
| <haskell>
| | Still, in order to understand them I studied, and I studied hard. I |
| | wanted to understand, it was difficult, and I kept studying. Going |
| | back to the foundation when needed. |
|
| |
|
| > newtype Eval_IO a = Eval_IO (a, O)
| | So, I cannot explain monads to you unless you are willing to study. I can |
| > deriving (Show)
| | show you the way, but you must take your time and follow that way. |
| > type O = String
| |
|
| |
|
| > instance Monad Eval_IO where
| | ==What do I need to know to understand monads?== |
| > 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)
| |
|
| |
|
| </haskell>
| | ===Functional programming=== |
|
| |
| Let's see the evaluator with output in action:
| |
| *TheMonadicWay> 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 - ")
| |
| *TheMonadicWay>
| |
|
| |
|
| Let's format the output part:
| | First you need at least a basic understanding of functional |
| eval (Con 6) <= 6
| | programming. |
| 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
| |
|
| |
|
| ==What Happened to Our Output??==
| | This is going to be the easiest step, because there is an invaluable |
| | resource available on line for free. |
|
| |
|
| Well, actually something happened to the output. Let's compare the
| | This is what I did: I spent 20 hours of my life watching the Video |
| output of evalMO (the monadic evaluator written without the
| | Lectures by Hal Abelson and Gerald Jay Sussman on |
| do-notation) and eval_IO:
| | [http://swiss.csail.mit.edu/classes/6.001/abelson-sussman-lectures/ Structure and Interpretation of Computer Programs]. |
|
| |
|
| *TheMonadicWay> evalMO (Con 6)
| | This course, and the annexed text book (I did not read it entirely), |
| (6,"eval (Con 6) <= 6 - ")
| | are an amazing introduction to computer science: you start by learning |
| *TheMonadicWay> eval_IO (Con 6)
| | some basic Scheme and then Abelson and Sussman will bring you, step by |
| Eval_IO (6,"eval (Con 6) <= 6 - ")
| | step, to understand evaluation, interpretation and compilation of Lisp |
| *TheMonadicWay>
| | (Scheme) code. |
|
| |
|
| They look almost the same, but they are not the same: the output of
| | The course is clear, interesting, funny and will provide you with a |
| eval_IO has the Eval_IO stuff. It must be related to the changes we
| | basic, but strong, understanding of functional programming. |
| had to do to our evaluator in order to use the do-conation, obviously.
| |
|
| |
|
| What's changed?
| | Believe me: if you like programming but don't have a computer science |
| | curriculum, you'll find out that spending 20 hours of your life to |
| | watch that course has been the most productive investment of your |
| | learning life. |
|
| |
|
| First the type definition. We have now:
| | ===My problem with Haskell=== |
|
| |
|
| <haskell>
| | I find Haskell an amazingly expressive programming language. It makes |
| newtype Eval_IO a = Eval_IO (a, O)
| | it incredibly easy to perform very difficult tasks, just like monads, |
| deriving (Show)
| | for instance. |
| </haskell>
| |
|
| |
|
| instead of
| | The problem is that, in doing so, it makes it difficult to understand |
| | Haskell to newcomers. |
|
| |
|
| <haskell>
| | I must confess that tutorials and other learning material are quite |
| type MO a = (a, Out)
| | dissatisfying on this regards too. |
| </haskell>
| |
| | |
| Moreover our bindMO and mkMO functions changed too, to reflect the
| |
| change of the type definition:
| |
|
| |
|
| <haskell>
| | Since Haskell seems to make easy what is not easy, these tutorial take |
| instance Monad Eval_IO where
| | the "it's easy" approach. |
| return a = Eval_IO (a, "")
| |
| (>>=) m f = Eval_IO (b, x ++ y)
| |
| where Eval_IO (a, x) = m
| |
| Eval_IO (b, y) = f a
| |
| </haskell>
| |
|
| |
|
| Now <hask>return a</hask> is the product of the application of the
| | I will give you an example. I think that the |
| type constructor Eval_IO to the pair that are going to form our monad. | | [http://www.cs.utah.edu/~hal/htut/ "Yet Another Haskell Tutorial"] is |
| | a really good attempt to explain Haskell, and if you want to |
| | understand this tutorial you need to read it at least for getting a |
| | good understanding of the Haskell type system. |
|
| |
|
| "return" takes an Int and insert it into our monad. It will also insert
| | The tutorial explains monads and explains the "do notation" in terms |
| a void String "" that (>>=) or (>>) will then concatenate in a
| | of lambda abstraction (par. 9.1, p. 120). Still, to the lambda |
| sequence of computations they glue together.
| | operator ("\") the tutorial dedicates only 17 lines in par. 4.4.1. |
| | | Moreover "\" is explained just as another way of creating functions. |
| The same for (>>=): it will now return something constructed by | |
| Eval_IO: "b", the result of the application of "f" to "a" (better, the
| |
| binding of "a" in "f") and "x" (matched by <hask>Eval_IO (a, x)</hask> with
| |
| the evaluation of "m") and "y", (matched by "Eval_IO(b,y)" with the
| |
| evaluation of "f a".
| |
| | |
| That is to say: in the "where" clause, we are matching for the
| |
| elements paired in a type Eval_IO: this is indeed the type of "m"
| |
| (corresponding to "eval_IO t" in the body of the evaluator) and "f a"
| |
| (where "f" correspond to another application of "eval_IO" to the
| |
| result of the previous application of "m").
| |
| | |
| And so, "Eval_IO (a,x) = m" means: match "a" and "x", paired in a type
| |
| Eval_IO, and that are produced by the evaluation of "m" (that is to
| |
| say: "eval_IO t"). The same for Eval_IO (b,y): match "b" and "y"
| |
| produced by the evaluation of "f a".
| |
| | |
| So the output of the evaluator is now not simply a pair made of and
| |
| Int and a String. It is a specific type (Eval_IO) that happens to
| |
| carry a pair of an Int and a String. But, if we want the Int and the
| |
| string, we have to extract them from the Eval_IO type, as we do in the
| |
| "where" clause: we ''unpack'' our type object (let's call it with its
| |
| name: our monad!) and take out the Int and the String to feed the next
| |
| function application and the output generation.
| |
| | |
| The same to insert something in our monad: if we want to create a pair
| |
| of an Int and a String, pair of type Eval_IO, we now have to ''pack''
| |
| the together by using our type constructor, feeding it with pair
| |
| composed by and Int and a String. This is what we do with the "return"
| |
| method of out monad and with "print_IO" function, where:
| |
| * return insert into the monad an Int;
| |
| * print_IO insert into the monad a String.
| |
| | |
| Notice that "combineM" disappeared. This is because it comes for free
| |
| by just defining our type Eval_IO as an instance of the Monad class.
| |
| | |
| Indeed, if we look at the definition of the Monad class in the Prelude we read:
| |
| <haskell>
| |
| class Monad m where
| |
| return :: a -> m a
| |
| (>>=) :: m a -> (a -> m b) -> m b
| |
| (>>) :: m a -> m b -> m b
| |
| fail :: String -> m a
| |
| | |
| -- Minimal complete definition: (>>=), return
| |
| p >> q = p >>= \ _ -> q
| |
| fail s = error s
| |
| </haskell>
| |
|
| |
| You can see that the "combineM"" method (or (>>)) is automatically derived by
| |
| the "bindMO" (or >>=) method:
| |
| | |
| <haskell>
| |
| p >> q = p >>= \ _ -> q
| |
| </haskell>
| |
| | |
| So, what the hell is the old <hask>type MO a = (a, Out)</hask> that
| |
| did not required all this additional work (apart the need to
| |
| specifically define (>>)?
| |
| | |
| Thanks the help of some nice guy of the
| |
| [http://www.haskell.org/mailman/listinfo/haskell-cafe haskell-cafe mailing list]
| |
| (look at the thread started by
| |
| [http://www.haskell.org/pipermail/haskell-cafe/2006-August/017634.html this silly question of mine])
| |
| we can answer.
| |
| | |
| Type MO is just a synonymous for (a,Out): the two can be substituted
| |
| one for the other. That's it.
| |
| | |
| We did not have to pack "a" and "Out" together with a type constructor
| |
| to have a new type MO.
| |
| | |
| As a consequence, we cannot use MO as an instance of Monad, and so, we
| |
| cannot use with it the syntactic sugar we needed: the do-notation.
| |
| | |
| That is to say: a type created with the "type" keyword cannot be an
| |
| instance of a class, and cannot inherits its methods (in our case
| |
| (>>=, >> and return). And without those methods the do-notation is not
| |
| usable.
| |
|
| |
| Anyway we will better understand all the far reaching consequences of
| |
| this new approach later on.
| |
| | |
| ==Errare Monadicum Est==
| |
| | |
| '''(Text to be done yet: just a summary)'''
| |
| | |
| In this section we will se how to handle exceptions in our monadic evaluator.
| |
| | |
| ===The basic evaluator, non monadic, with exception===
| |
| | |
| <haskell>
| |
| | |
| > data M a = Raise Exception
| |
| > | Return a
| |
| > deriving (Show)
| |
| > type Exception = String
| |
| | |
| > evalE :: Term -> M Int
| |
| > evalE (Con a) = Return a
| |
| > evalE (Add a b) =
| |
| > case evalE a of
| |
| > Raise e -> Raise e
| |
| > Return a ->
| |
| > case evalE b of
| |
| > Raise e -> Raise e
| |
| > Return b ->
| |
| > if (a+b) == 42
| |
| > then Raise "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > else Return (a+b)
| |
| | |
| </haskell>
| |
| | |
| Test it with:
| |
| | |
| evalE (Add (Con 10) (Add (Add (Con 20) (Con 10)) (Con 2)))
| |
| | |
| ===The basic evaluator, monadic, with exceptions===
| |
| | |
| <haskell>
| |
| | |
| > data M1 a = Except Exception
| |
| > | Ok {showM :: a }
| |
| > deriving (Show)
| |
| | |
| > instance Monad M1 where
| |
| > return a = Ok a
| |
| > m >>= f = case m of
| |
| > Except e -> Except e
| |
| > Ok a -> f a
| |
| | |
| > raise :: Exception -> M1 a
| |
| > raise e = Except e
| |
| | |
| > eval_ME :: Term -> M1 Int
| |
| > eval_ME (Con a) = do return a
| |
| > eval_ME (Add t u) = do a <- eval_ME t
| |
| > b <- eval_ME u
| |
| > if (a+b) == 42
| |
| > then raise "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > else return (a + b)
| |
| | |
| </haskell>
| |
| | |
| Run with:
| |
| | |
| eval_ME (Add (Con 10) (Add (Add (Con 20) (Con 10)) (Con 2)))
| |
| | |
| It is noteworthy the fact that in our datatype definition we used a
| |
| label field with a label selector (we called it showM).
| |
| | |
| Just to refresh your memory:
| |
| | |
| <haskell>
| |
| | |
| > data Person = Person {name :: String,
| |
| > age :: Int,
| |
| > hobby :: String
| |
| > } deriving (Show)
| |
|
| |
| > andreaRossato = Person "Andrea" 37 "Haskell The Monadic Way"
| |
| > personName (Person a b c) = a
| |
| | |
| </haskell>
| |
| | |
| will produce:
| |
| *TheMonadicWay> andreaRossato
| |
| Person {name = "Andrea", age = 37, hobby = "Haskell The Monadic Way"}
| |
| *TheMonadicWay> personName andreaRossato
| |
| "Andrea"
| |
| *TheMonadicWay> name andreaRossato
| |
| "Andrea"
| |
| *TheMonadicWay> age andreaRossato
| |
| 37
| |
| *TheMonadicWay> hobby andreaRossato
| |
| "Haskell The Monadic Way"
| |
| *TheMonadicWay>
| |
| | |
| | |
| ===Monadic evaluator with output and exceptions===
| |
| | |
| This is the evaluator that produces output, plus exceptions.
| |
| | |
| <haskell>
| |
| | |
| > data M2 a = Ex Exception
| |
| > | Done {unpack :: (a,O) }
| |
| > deriving (Show)
| |
| | |
| > instance Monad M2 where
| |
| > return a = Done (a, "")
| |
| > m >>= f = case m of
| |
| > Ex e -> Ex e
| |
| > Done (a, x) -> case (f a) of
| |
| > Ex e1 -> Ex e1
| |
| > Done (b, y) -> Done (b, x ++ y)
| |
| | |
| </haskell>
| |
| Since we have to concatenate output we must check that also the next
| |
| run of the evaluator will not raise an exception.
| |
| <haskell>
| |
|
| |
| > raise_IOE :: Exception -> M2 a
| |
| > raise_IOE e = Ex e
| |
| | |
| > print_IOE :: O -> M2 ()
| |
| > print_IOE x = Done ((), x)
| |
|
| |
| > eval_IOE :: Term -> M2 Int
| |
| > eval_IOE (Con a) = do print_IOE (formatLine (Con a) a)
| |
| > return a
| |
| > eval_IOE (Add t u) = do a <- eval_IOE t
| |
| > b <- eval_IOE u
| |
| > let out = formatLine (Add t u) (a + b)
| |
| > print_IOE out
| |
| > if (a+b) == 42
| |
| > then raise_IOE $ out ++ "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > else return (a + b)
| |
| | |
| </haskell>
| |
| | |
| Run with
| |
| | |
| eval_IOE (Add (Con 10) (Add (Add (Con 20) (Con 10)) (Con 2)))
| |
| | |
| Look at the let clause within the do notation: we do not need let
| |
| since all variable bound within a do procedure will be available all
| |
| the way down.
| |
| | |
| Remember m >>= \a -> f >>= \ -> ...
| |
| | |
| ==We Need A State==
| |
| | |
| We start adding complexity to our monadic evaluator. But in order to
| |
| add a counter we will start over again (to review out knowledeg).
| |
| | |
| ===The basic evaluator, non monadic, with a counter===
| |
|
| |
| The basic evaluator plus a counter: evalNM takes now the expression to
| |
| be evaluated plus an initial state (0) to start counting from.
| |
| | |
| <haskell>
| |
| | |
| > -- non monadic
| |
| > evalNMS :: Term -> MS Int
| |
| > evalNMS (Con a) x = (a, x + 1)
| |
| > evalNMS (Add t u) x = let (a, y) = evalNMS t x in
| |
| > let (b, z) = evalNMS u y in
| |
| > (a + b, z +1)
| |
| | |
| </haskell>
| |
| | |
| ===The evaluator, monadic, with a counter, without do-notation===
| |
| The moadic version without do notation.
| |
| | |
| <haskell>
| |
| | |
| > -- monadic
| |
| | |
| > type MS a = State -> (a, State)
| |
| > type State = Int
| |
| | |
| > mkMS :: a -> MS a
| |
| > mkMS a = \x -> (a, x)
| |
| | |
| > bindMS :: MS a -> (a -> MS b) -> MS b
| |
| > bindMS m f = \x ->
| |
| > let (a, y) = m x in
| |
| > let (b, z) = f a y in
| |
| > (b, z)
| |
| | |
| > combineMS :: MS a -> MS b -> MS b
| |
| > combineMS m f = m `bindMS` \_ -> f
| |
|
| |
| > incState :: MS ()
| |
| > incState = \s -> ((), s + 1)
| |
| | |
| > evalMS :: Term -> MS Int
| |
| > evalMS (Con a) = incState `combineMS` mkMS a
| |
| > evalMS (Add t u) = evalMS t `bindMS` \a ->
| |
| > evalMS u `bindMS` \b ->
| |
| > incState `combineMS` mkMS (a + b)
| |
| | |
| > --evalMS (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) 0
| |
| | |
| </haskell>
| |
| | |
| ===The evaluator, monadic, with counter and output, without do-notation===
| |
| | |
| Now we'll add Output to the stateful evaluator:
| |
| | |
| <haskell>
| |
| | |
| > -- state and output
| |
| | |
| > type MSO a = State -> (a, State, Output)
| |
| | |
| > mkMSO :: a -> MSO a
| |
| > mkMSO a = \s -> (a, s, "")
| |
| | |
| > bindMSO :: MSO a -> (a -> MSO b) -> MSO b
| |
| > bindMSO m f = \x ->
| |
| > let (a, y, s1) = m x in
| |
| > let (b, z, s2) = f a y in
| |
| > (b, z, s1 ++ s2)
| |
| | |
| > combineMSO :: MSO a -> MSO b -> MSO b
| |
| > combineMSO m f = m `bindMSO` \_ -> f
| |
| | |
| > incMSOstate :: MSO ()
| |
| > incMSOstate = \s -> ((), s + 1, "")
| |
| | |
| > outMSO :: Output -> MSO ()
| |
| > outMSO = \x s -> ((),s, x)
| |
| | |
| > evalMSO :: Term -> MSO Int
| |
| > evalMSO (Con a) = incMSOstate `combineMSO`
| |
| > outMSO (formatLine (Con a) a) `combineMSO`
| |
| > mkMSO a
| |
| > evalMSO (Add t u) = evalMSO t `bindMSO` \a ->
| |
| > evalMSO u `bindMSO` \b ->
| |
| > incMSOstate `combineMSO`
| |
| > outMSO (formatLine (Add t u) (a + b)) `combineMSO`
| |
| > mkMSO (a + b)
| |
| | |
| > --evalMSO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12)))) 0
| |
| | |
| </haskell>
| |
| | |
| ===The monadic evaluator with output and counter in do-notation===
| |
| | |
| State, Output in do-notation. Look at how much the complexity of our
| |
| (>>=) founction is increasing:
| |
| | |
| <haskell>
| |
| | |
| > -- thanks to Brian Hulley
| |
| | |
| > newtype MSIO a = MSIO (State -> (a, State, Output))
| |
| > instance Monad MSIO where
| |
| > return a = MSIO (\s -> (a, s, ""))
| |
| > (MSIO m) >>= f = MSIO $ \x ->
| |
| > let (a, y, s1) = m x in
| |
| > let MSIO runNextStep = f a in
| |
| > let (b, z, s2) = runNextStep y in
| |
| > (b, z, s1 ++ s2)
| |
| | |
| | |
| > incMSOIstate :: MSIO ()
| |
| > incMSOIstate = MSIO (\s -> ((), s + 1, ""))
| |
| | |
| > print_MSOI :: Output -> MSIO ()
| |
| > print_MSOI x = MSIO (\s -> ((),s, x))
| |
| | |
| > eval_MSOI :: Term -> MSIO Int
| |
| > eval_MSOI (Con a) = do incMSOIstate
| |
| > print_MSOI (formatLine (Con a) a)
| |
| > return a
| |
| | |
| > eval_MSOI (Add t u) = do a <- eval_MSOI t
| |
| > b <- eval_MSOI u
| |
| > incMSOIstate
| |
| > print_MSOI (formatLine (Add t u) (a + b))
| |
| > return (a + b)
| |
| | |
| > run_MSOI :: MSIO a -> State -> (a, State, Output)
| |
| > run_MSOI (MSIO f) s = f s
| |
| | |
| > --run_MSOI (eval_MSOI (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12))))) 0
| |
| | |
| </haskell>
| |
| | |
| ===Another version of the monadic evaluator with output and counter, in do-notation===
| |
| | |
| This is e second version that exploit label fields in datatype to
| |
| decrease the complexity of the binding operations.
| |
| | |
| <haskell>
| |
| | |
| > -- Thanks Udo Stenzel
| |
| | |
| > newtype Eval_SIO a = Eval_SIO { unPackMSIOandRun :: State -> (a, State, Output) }
| |
| > instance Monad Eval_SIO where
| |
| > return a = Eval_SIO (\s -> (a, s, ""))
| |
| > (>>=) m f = Eval_SIO (\x ->
| |
| > let (a, y, s1) = unPackMSIOandRun m x in
| |
| > let (b, z, s2) = unPackMSIOandRun (f a) y in
| |
| > (b, z, s1 ++ s2))
| |
| | |
| > incSIOstate :: Eval_SIO ()
| |
| > incSIOstate = Eval_SIO (\s -> ((), s + 1, ""))
| |
| | |
| > print_SIO :: Output -> Eval_SIO ()
| |
| > print_SIO x = Eval_SIO (\s -> ((),s, x))
| |
| | |
| > eval_SIO :: Term -> Eval_SIO Int
| |
| > eval_SIO (Con a) = do incSIOstate
| |
| > print_SIO (formatLine (Con a) a)
| |
| > return a
| |
| > eval_SIO (Add t u) = do a <- eval_SIO t
| |
| > b <- eval_SIO u
| |
| > incSIOstate
| |
| > print_SIO (formatLine (Add t u) (a + b))
| |
| > return (a + b)
| |
| | |
| > --unPackMSIOandRun (eval_SIO (Add (Con 6) (Add (Con 16) (Add (Con 20) (Con 12))))) 0
| |
| | |
| </haskell>
| |
| | |
| | |
| ==If There's A State We Need Some Discipline: Dealing With Complexity==
| |
| | |
| In order to increase the complexity of our monad now we will try to
| |
| mix State (counter), Exceptions and Output.
| |
| | |
| This is an email [http://www.haskell.org/pipermail/haskell-cafe/2006-August/017672.html I send to the haskell-cafe mailing list]:
| |
| | |
| <pre>
| |
| Now I'm trying to create a statefull evaluator, with output and
| |
| exception, but I'm facing a problem I seem not to be able to
| |
| conceptually solve.
| |
| | |
| Take the code below.
| |
| Now, in order to get it run (and try to debug) the Eval_SOI type has a
| |
| Raise constructor that produces the same type of SOIE. Suppose instead it
| |
| should be constructing something like Raise "something".
| |
| Moreover, I wrote a second version of >>=, commented out.
| |
| This is just to help me illustrate to problem I'm facing.
| |
| | |
| Now, >>= is suppose to return Raise if "m" is matched against Raise
| |
| (second version commented out).
| |
| If "m" matches SOIE it must return a SOIE only if "f a" does not
| |
| returns a Raise (output must be concatenated).
| |
| | |
| I seem not to be able to find a way out. Moreover, I cannot understand
| |
| if a way out can be possibly found. Something suggests me it could be
| |
| related to that Raise "something".
| |
| But my feeling is that functional programming could be something out
| |
| of the reach of my mind... by the way, I teach Law, so perhaps you'll
| |
| forgive me...;-)
| |
| | |
| If you can help me to understand this problem all I can promise is
| |
| that I'll mention your help in the tutorial I'm trying to write on
| |
| "the monadic way"... that seems to lead me nowhere.
| |
| | |
| Thanks for your kind attention.
| |
| | |
| Andrea
| |
| </pre>
| |
| | |
| This was the code:
| |
| | |
| <haskell>
| |
| data Eval_SOI a = Raise { unPackMSOIandRun :: State -> (a, State, Output) }
| |
| | SOIE { unPackMSOIandRun :: State -> (a, State, Output) }
| |
| | |
| instance Monad Eval_SOI where
| |
| return a = SOIE (\s -> (a, s, ""))
| |
| m >>= f = SOIE (\x ->
| |
| let (a, y, s1) = unPackMSOIandRun m x in
| |
| case f a of
| |
| SOIE nextRun -> let (b, z, s2) = nextRun y in
| |
| (b, z, s1 ++ s2)
| |
| Raise e1 -> e1 y --only this happens
| |
| | |
| )
| |
| -- (>>=) m f = case m of
| |
| -- Raise e -> error "ciao" -- why this is not going to happen?
| |
| -- SOIE a -> SOIE (\x ->
| |
| -- let (a, y, s1) = unPackMSOIandRun m x in
| |
| -- let (b, z, s2) = unPackMSOIandRun (f a) y in
| |
| -- (b, z, s1 ++ s2))
| |
| | |
| | |
| incSOIstate :: Eval_SOI ()
| |
| incSOIstate = SOIE (\s -> ((), s + 1, ""))
| |
| | |
| print_SOI :: Output -> Eval_SOI ()
| |
| print_SOI x = SOIE (\s -> ((),s, x))
| |
| | |
| raise x e = Raise (\s -> (x,s,e))
| |
| | |
| eval_SOI :: Term -> Eval_SOI Int
| |
| eval_SOI (Con a) = do incSOIstate
| |
| print_SOI (formatLine (Con a) a)
| |
| return a
| |
| eval_SOI (Add t u) = do a <- eval_SOI t
| |
| b <- eval_SOI u
| |
| incSOIstate
| |
| print_SOI (formatLine (Add t u) (a + b))
| |
| if (a + b) == 42
| |
| then raise (a+b) " = The Ultimate Answer!!"
| |
| else return (a + b)
| |
| | |
| runEval exp = case eval_SOI exp of
| |
| Raise a -> a 0
| |
| SOIE p -> let (result, state, output) = p 0 in
| |
| (result,state,output)
| |
| | |
| | |
| | |
| --runEval (Add (Con 10) (Add (Con 28) (Add (Con 40) (Con 2))))
| |
| </haskell>
| |
| | |
| This code will produce
| |
| | |
| eval (Con 10) <= 10 -
| |
| eval (Con 28) <= 28 -
| |
| eval (Con 40) <= 40 -
| |
| eval (Con 2) <= 2 - = The Ultimate Answer!!
| |
| eval (Add (Con 28) (Add (Con 40) (Con 2))) <= 70 -
| |
| eval (Add (Con 10) (Add (Con 28) (Add (Con 40) (Con 2)))) <= 80 -
| |
| | |
| The exception appears in the output, but executioon is not stopped.
| |
| | |
| ===Monadic evaluator with output, counter and exception, in do-notation===
| |
| | |
| Brian Hulley [http://www.haskell.org/pipermail/haskell-cafe/2006-August/017680.html came up with this solution]:
| |
| | |
| <haskell>
| |
| | |
| > -- thanks to Brian Hulley
| |
| > data Result a
| |
| > = Good a State Output
| |
| > | Bad State Output Exception
| |
| > deriving Show
| |
| | |
| > newtype Eval_SIOE a = SIOE {runSIOE :: State -> Result a}
| |
| | |
| > instance Monad Eval_SIOE where
| |
| > return a = SIOE (\s -> Good a s "")
| |
| > m >>= f = SIOE $ \x ->
| |
| > case runSIOE m x of
| |
| > Good a y o1 ->
| |
| > case runSIOE (f a) y of
| |
| > Good b z o2 -> Good b z (o1 ++ o2)
| |
| > Bad z o2 e -> Bad z (o1 ++ o2) e
| |
| > Bad z o2 e -> Bad z o2 e
| |
| | |
| > raise_SIOE e = SIOE (\s -> Bad s "" e)
| |
| | |
| > incSIOEstate :: Eval_SIOE ()
| |
| > incSIOEstate = SIOE (\s -> Good () (s + 1) "")
| |
| | |
| > print_SIOE :: Output -> Eval_SIOE ()
| |
| > print_SIOE x = SIOE (\s -> Good () s x)
| |
| | |
| | |
| > eval_SIOE :: Term -> Eval_SIOE Int
| |
| > eval_SIOE (Con a) = do incSIOEstate
| |
| > print_SIOE (formatLine (Con a) a)
| |
| > return a
| |
| > eval_SIOE (Add t u) = do a <- eval_SIOE t
| |
| > b <- eval_SIOE u
| |
| > incSIOEstate
| |
| > let out = formatLine (Add t u) (a + b)
| |
| > print_SIOE out
| |
| > if (a+b) == 42
| |
| > then raise_SIOE $ out ++ "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > else return (a + b)
| |
| | |
| > runEval exp = case runSIOE (eval_SIOE exp) 0 of
| |
| > Bad s o e -> "Error at iteration n. " ++ show s ++
| |
| > " - Output stack = " ++ o ++
| |
| > " - Exception = " ++ e
| |
| > Good a s o -> "Result = " ++ show a ++
| |
| > " - Iterations = " ++ show s ++ " - Output = " ++ o
| |
| | |
| </haskell>
| |
| | |
| Run with runEval (Add (Con 18) (Add (Con 12) (Add (Con 10) (Con 2))))
| |
| | |
| ==Taking Complexity Out of a Monad: Monadic Transformers==
| |
| | |
| We have seen how the complexity of (>>=) was growing by adding
| |
| operations to be done.
| |
| N
| |
| We will do the opposite: we will implement a state transformer (I
| |
| copied StateT).
| |
| | |
| We will embed our monad in the StateT monad and we will start moving
| |
| state and output from the inner monad (our one) to the outer monad
| |
| (StateT).
| |
| | |
| ===The StateT Monad: a Monad Container===
| |
| Let me introduce StateT with some useful functions:
| |
| | |
| <haskell>
| |
| | |
| > newtype StateT s m a = StateT {runStateT :: s -> m (a,s) } --StateT (s -> m (a,s))
| |
| | |
| > instance Monad m => Monad (StateT s m) where
| |
| > return a = StateT (\s -> return (a,s))
| |
| > StateT m1 >>= k = StateT (\s -> do ~(a,s1) <- m1 s
| |
| > let StateT m2 = k a
| |
| > m2 s1)
| |
| | |
| > -- | Execute a stateful computation, as a result we get
| |
| > -- the result of the computation, and the final state.
| |
| > runState :: s -> StateT s m a -> m (a,s)
| |
| > runState s (StateT m) = m s
| |
| | |
| > -- | Execute a stateful computation, ignoring the final state.
| |
| > evalState :: Functor m => s -> StateT s m a -> m a
| |
| > evalState s m = fmap fst (runState s m)
| |
| | |
| > -- | Execute a stateful computation, just for the side effect.
| |
| > execState :: Functor m => s -> StateT s m a -> m s
| |
| > execState s m = fmap snd (runState s m)
| |
| | |
| | |
| > lift :: (Monad m) => m a -> StateT s m a
| |
| > lift m = StateT (\s -> do x <- m
| |
| > return (x,s))
| |
| | |
| </haskell>
| |
| | |
| StateT is pleased to meet you!.
| |
| | |
| ===StateT as a counter, and monadic evaluator with output and exceptions===
| |
| And now out monad, with state out from it:
| |
| | |
| <haskell>
| |
| | |
| > data MTa a = FailTa Exception
| |
| > | DoneTa {unpackDoneTa :: (a,O) }
| |
| > deriving (Show)
| |
| | |
| | |
| > instance Monad MTa where
| |
| > return a = DoneTa (a, "")
| |
| > m >>= f = case m of
| |
| > FailTa e -> FailTa e
| |
| > DoneTa (a, x) -> case (f a) of
| |
| > FailTa e1 -> FailTa e1
| |
| > DoneTa (b, y) -> DoneTa (b, x ++ y)
| |
| | |
| > instance Functor MTa where
| |
| > fmap _ (FailTa e) = FailTa e
| |
| > fmap f (DoneTa (r,o)) = DoneTa ((f r),o)
| |
| | |
| > raiseTa_SIOE :: O -> StateT Int MTa a
| |
| > raiseTa_SIOE e = lift (FailTa e)
| |
| | |
| > printTa_SIOE :: O -> StateT Int MTa ()
| |
| > printTa_SIOE x = lift (DoneTa ((), x))
| |
| | |
| > incTaState :: StateT Int MTa ()
| |
| > incTaState = StateT (\s -> return ((), s + 1))
| |
| | |
| > evalTa_SIOE :: Term -> StateT Int MTa Int
| |
| > evalTa_SIOE (Con a) = do incTaState
| |
| > printTa_SIOE (formatLine (Con a) a)
| |
| > return a
| |
| > evalTa_SIOE (Add t u) = do a <- evalTa_SIOE t
| |
| > b <- evalTa_SIOE u
| |
| > incTaState
| |
| > let out = formatLine (Add t u) (a + b)
| |
| > printTa_SIOE out
| |
| > if (a+b) == 42
| |
| > then raiseTa_SIOE $
| |
| > out ++ "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > else return (a + b)
| |
| | |
| > runEvalTa :: Term -> String
| |
| > runEvalTa exp = case runStateT (evalTa_SIOE exp) 0 of
| |
| > FailTa e -> e
| |
| > DoneTa (~(r,s),o)-> "Result = " ++ show r ++
| |
| > "; Iteration = " ++ show s ++
| |
| > "; Output = " ++ o
| |
| | |
| > runEvalTa1 :: Term -> String
| |
| > runEvalTa1 exp = case runState 0 (evalTa_SIOE exp) of
| |
| > FailTa e -> e
| |
| > DoneTa ((r,s),o) -> "Result = " ++ show r ++
| |
| > "; Iteration = " ++ show s ++
| |
| > "; Output = " ++ o
| |
|
| |
| > runEvalTa2 :: Term -> String
| |
| > runEvalTa2 exp = case evalState 0 (evalTa_SIOE exp) of
| |
| > FailTa e -> e
| |
| > DoneTa (r,o) -> "Result = " ++ show r ++ "; Output = " ++ o
| |
| | |
| > runEvalTa3 :: Term -> String
| |
| > runEvalTa3 exp = case execState 0 (evalTa_SIOE exp) of
| |
| > FailTa e -> e
| |
| > DoneTa (s,o) -> "Iterations = " ++ show s ++ "; Output = " ++ o
| |
| | |
| </haskell>
| |
| | |
| ===StateT to keep output and counter, and monadic evaluator with (only) exceptions===
| |
| | |
| Now we take output away from the inner monad and place it in the outer
| |
| one (StateT):
| |
| | |
| <haskell>
| |
| | |
| | |
| > data MTb a = FailTb Exception
| |
| > | DoneTb {unpackDoneTb :: a }
| |
| > deriving (Show)
| |
| | |
| > type StateIO = (O,Int)
| |
| | |
| > instance Monad MTb where
| |
| > return a = DoneTb a
| |
| > m >>= f = case m of
| |
| > FailTb e -> FailTb e
| |
| > DoneTb a -> f a
| |
| | |
| > instance Functor MTb where
| |
| > fmap _ (FailTb e) = FailTb e
| |
| > fmap f (DoneTb b) = DoneTb (f b)
| |
| | |
| | |
| > raiseTb_SIOE :: O -> StateT StateIO MTb a
| |
| > raiseTb_SIOE e = lift (FailTb e)
| |
| | |
| > printTb_SIOE :: O -> StateT StateIO MTb ()
| |
| > printTb_SIOE x = StateT (\(o,s) -> return ((), (o ++ x,s)))
| |
| | |
| > incTbStateIO :: StateT StateIO MTb ()
| |
| > incTbStateIO = StateT (\(o,s) -> return ((), (o,s + 1)))
| |
| | |
| > evalTb_SIOE :: Term -> StateT StateIO MTb Int
| |
| > evalTb_SIOE (Con a) = do incTbStateIO
| |
| > printTb_SIOE (formatLine (Con a) a)
| |
| > return a
| |
| > evalTb_SIOE (Add t u) = do a <- evalTb_SIOE t
| |
| > b <- evalTb_SIOE u
| |
| > incTbStateIO
| |
| > let out = formatLine (Add t u) (a + b)
| |
| > printTb_SIOE out
| |
| > if (a+b) == 42
| |
| > then raiseTb_SIOE $
| |
| > out ++ "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > else return (a + b)
| |
| | |
| </haskell>
| |
| | |
| We take away complexity from >>= and put it in the function we need
| |
| to use to manipulate content in our StateT monad.
| |
| | |
| These are some wrapper to the evaluator to get the result and the
| |
| side-effects produced by evaluation:
| |
| | |
| <haskell>
| |
| | |
| > runEvalTb :: Term -> String
| |
| > runEvalTb exp = case runStateT (evalTb_SIOE exp) ("",0) of
| |
| > FailTb e -> e
| |
| > DoneTb (r,~(o,s)) -> "Result = " ++ show r ++
| |
| > "; Iteration = " ++ show s ++
| |
| > "; Output = " ++ o
| |
| | |
| | |
| > runEvalTb1 :: Term -> String
| |
| > runEvalTb1 exp = case runState ("",0) (evalTb_SIOE exp) of
| |
| > FailTb e -> e
| |
| > DoneTb (r,~(o,s)) -> "Result = " ++ show r ++
| |
| > "; Iteration = " ++ show s ++
| |
| > "; Output = " ++ o
| |
|
| |
| > runEvalTb2 :: Term -> String
| |
| > runEvalTb2 exp = case evalState ("",0) (evalTb_SIOE exp) of
| |
| > FailTb e -> e
| |
| > DoneTb r -> "Result = " ++ show r
| |
| | |
| > runEvalTb3 :: Term -> String
| |
| > runEvalTb3 exp = case execState ("",0) (evalTb_SIOE exp) of
| |
| > FailTb e -> e
| |
| > DoneTb (o,s) -> "Iterations = " ++ show s ++
| |
| > " - Output = " ++ o
| |
| | |
| </haskell>
| |
| | |
| ===StateT to keep output, counter and debug. The monadic evaluator is only for failable computations===
| |
| | |
| And now we will keep in the inner monad only the result of the evaluation.
| |
| | |
| <haskell>
| |
| | |
| > data MT a = FailT Exc
| |
| > | DoneT {unpackDoneT :: a }
| |
| > deriving (Show)
| |
| | |
| > type Exc = String
| |
| > type IOstack = [Output]
| |
| > newtype StateTIO = StateTIO {unPackStateTIO :: (IOstack,Exc,Int)}
| |
| > deriving(Show)
| |
| | |
| > instance Monad MT where
| |
| > return a = DoneT a
| |
| > m >>= f = case m of
| |
| > FailT e -> FailT e
| |
| > DoneT a -> f a
| |
| | |
| > instance Functor MT where
| |
| > fmap _ (FailT a) = FailT a
| |
| > fmap f (DoneT a) = DoneT (f a)
| |
| | |
| </haskell>
| |
| | |
| Simple isn't it?
| |
| | |
| The complexity is now below:
| |
| | |
| <haskell>
| |
| | |
| > stopExecT_SIOE :: Output -> StateT StateTIO MT Int
| |
| > stopExecT_SIOE exc = StateT (\s -> do x <- FailT exc
| |
| > return (x, s))
| |
| | |
| > catchT_SIOE exc = StateT (\(StateTIO (o,e,s)) ->
| |
| > return ((), StateTIO (o ,"Exception at Iteration " ++
| |
| > show s ++ ": " ++ exc ++ " - " ++ e,s)))
| |
| | |
| > printT_SIOE :: Output -> StateT StateTIO MT ()
| |
| > printT_SIOE x = StateT (\(StateTIO (o,e,s)) -> return ((), StateTIO (x:o,e,s)))
| |
| | |
| > incTstateIO :: StateT StateTIO MT ()
| |
| > incTstateIO = StateT (\(StateTIO (o,e,s)) -> return ((),StateTIO (o,e,s + 1)))
| |
| | |
| > evalT_SIOE :: Term -> StateT StateTIO MT Int
| |
| > evalT_SIOE (Con a) = do incTstateIO
| |
| > printT_SIOE (formatLine (Con a) a)
| |
| > return a
| |
| > evalT_SIOE (Add t u) = do a <- evalT_SIOE t
| |
| > b <- evalT_SIOE u
| |
| > incTstateIO
| |
| > let out = formatLine (Add t u) (a + b)
| |
| > printT_SIOE out
| |
| > case (a+b) of
| |
| > 42 -> do catchT_SIOE "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| > return (a+b)
| |
| > 11 -> stopExecT_SIOE "11.... I do not like this number!"
| |
| > otherwise -> return (a + b)
| |
| | |
| </haskell>
| |
| | |
| But now we have exceptions to stop execution and debugging output.
| |
| | |
| Some helper functions:
| |
| | |
| <haskell>
| |
| | |
| > runEvalT :: Term -> String
| |
| > runEvalT exp = case runStateT (evalT_SIOE exp) (StateTIO ([],"",0)) of
| |
| > FailT e -> e
| |
| > DoneT (r,StateTIO (o,e,s)) -> "Result = " ++ show r ++ "; Iteration = " ++ show s ++
| |
| > "; Output = " ++ show o ++ " - Exceptions = " ++ e
| |
| | |
| | |
| > runEvalT1 :: Term -> String
| |
| > runEvalT1 exp = case runState (StateTIO ([],"",0)) (evalT_SIOE exp) of
| |
| > FailT e -> e
| |
| > DoneT (r,StateTIO(o,e,s)) -> "Result = " ++ show r ++ "; Iteration = " ++ show s
| |
| > ++ "; Output = " ++ show o ++ " - Exceptions = " ++ e
| |
|
| |
| > runEvalT2 :: Term -> String
| |
| > runEvalT2 exp = case evalState (StateTIO ([],"",0)) (evalT_SIOE exp) of
| |
| > FailT e -> e
| |
| > DoneT r -> "Result = " ++ show r
| |
| | |
| > runEvalT3 :: Term -> String
| |
| > runEvalT3 exp = case execState (StateTIO ([],"",0)) (evalT_SIOE exp) of
| |
| > FailT e -> e
| |
| > DoneT (StateTIO (o,e,s)) -> "Iterations = " ++ show s ++
| |
| | |
| > " - Output = " ++ show o ++ " - Exceptions = " ++ e
| |
| > showOut :: [String] -> IO ()
| |
| > showOut [] = return ()
| |
| > showOut (a:xs) = do print a
| |
| > showOut xs
| |
| | |
| > runMyEval :: Term -> IO ()
| |
| > runMyEval exp = let StateTIO (a,b,c) = unpackDoneT $ execState (StateTIO ([],"",0)) (evalT_SIOE exp) in
| |
| > showOut $ reverse a
| |
| | |
| </haskell>
| |
| | |
| Some tests:
| |
| <pre>
| |
| *TheMonadicWay> runEvalT (Add (Con 18) (Add (Con 12) (Add (Con 10) (Con 2))))
| |
| "Result = 42; Iteration = 7; Output = [\"eval (Add (Con 18) (Add (Con 12) (Add (Con 10) (Con 2)))) <= 42 - \",
| |
| \"eval (Add (Con 12) (Add (Con 10) (Con 2))) <= 24 - \",
| |
| \"eval (Add (Con 10) (Con 2)) <= 12 - \",
| |
| \"eval (Con 2) <= 2 - \",
| |
| \"eval (Con 10) <= 10 - \",
| |
| \"eval (Con 12) <= 12 - \",
| |
| \"eval (Con 18) <= 18 - \"] -
| |
| Exceptions = Exception at Iteration 7: The Ultimate Answer Has Been Computed!! Now I'm tired! - "
| |
| *TheMonadicWay> runEvalT2 (Add (Con 18) (Add (Con 12) (Add (Con 10) (Con 2))))
| |
| "Result = 42"
| |
| *TheMonadicWay> runEvalT3 (Add (Con 18) (Add (Con 12) (Add (Con 10) (Con 2))))
| |
| "Iterations = 7 - Output = [\"eval (Add (Con 18) (Add (Con 12) (Add (Con 10) (Con 2)))) <= 42 - \",
| |
| \"eval (Add (Con 12) (Add (Con 10) (Con 2))) <= 24 - \",
| |
| \"eval (Add (Con 10) (Con 2)) <= 12 - \",
| |
| \"eval (Con 2) <= 2 - \",
| |
| \"eval (Con 10) <= 10 - \",
| |
| \"eval (Con 12) <= 12 - \",
| |
| \"eval (Con 18) <= 18 - \"] -
| |
| Exceptions = Exception at Iteration 7: The Ultimate Answer Has Been Computed!! Now I'm tired! - "
| |
| *TheMonadicWay> runEvalT3 (Add (Con 1) (Add (Con 7) (Add (Con 1) (Con 2))))
| |
| "Iterations = 7 - Output = [\"eval (Add (Con 1) (Add (Con 5) (Add (Con 1) (Con 2)))) <= 9 - \",
| |
| \"eval (Add (Con 5) (Add (Con 1) (Con 2))) <= 8 - \",
| |
| \"eval (Add (Con 1) (Con 2)) <= 3 - \",
| |
| \"eval (Con 2) <= 2 - \",
| |
| \"eval (Con 1) <= 1 - \",
| |
| \"eval (Con 5) <= 5 - \",
| |
| \"eval (Con 1) <= 1 - \"] - Exceptions = "
| |
| *TheMonadicWay> runEvalT3 (Add (Con 1) (Add (Con 7) (Add (Con 1) (Con 2))))
| |
| "11.... I do not like this number!"
| |
| *TheMonadicWay> runMyEval (Add (Add (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) (Con 3)) (Con 10))
| |
| "eval (Con 10) <= 10 - "
| |
| "eval (Con 2) <= 2 - "
| |
| "eval (Add (Con 10) (Con 2)) <= 12 - "
| |
| "eval (Con 12) <= 12 - "
| |
| "eval (Con 3) <= 3 - "
| |
| "eval (Add (Con 12) (Con 3)) <= 15 - "
| |
| "eval (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) <= 27 - "
| |
| "eval (Con 3) <= 3 - "
| |
| "eval (Add (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) (Con 3)) <= 30 - "
| |
| "eval (Con 10) <= 10 - "
| |
| "eval (Add (Add (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) (Con 3)) (Con 10)) <= 40 - "
| |
| *TheMonadicWay>
| |
| </pre>
| |
| | |
| | |
| ==The Final Cut==
| |
| | |
| ===StateT for output, counter, debug, using the Standard Library===
| |
| | |
| <haskell>
| |
| module MyStateT where
| |
| import Control.Monad.State hiding (State)
| |
| | |
| data Term = Con Int
| |
| | Add Term Term
| |
| deriving (Show)
| |
| | |
| type IOStack = [Output]
| |
| type Output = String
| |
| type Debug = [String]
| |
| data EvalST = State {getIOS :: IOStack, getDebug :: Debug, getCount:: Int}
| |
| deriving(Show)
| |
| | |
| | |
| type Exception = String
| |
| data MT a = Fail Exception
| |
| | Done {unpackDone :: a }
| |
| deriving (Show)
| |
| | |
| type Eval s a = StateT s MT a
| |
| | |
| instance Monad MT where
| |
| return a = Done a
| |
| m >>= f = case m of
| |
| Fail e -> Fail e
| |
| Done a -> f a
| |
| | |
| instance Functor MT where
| |
| fmap _ (Fail a) = Fail a
| |
| fmap f (Done a) = Done (f a)
| |
| | |
| emptyState = State [] [] 0
| |
| | |
| stopExecT exc = lift $ Fail exc
| |
| | |
| catchT e = do st <- get
| |
| let s = getCount st
| |
| let es = getDebug st
| |
| let o = getIOS st
| |
| let exc = "Debug msg at Iteration " ++ show s ++ ": " ++ e
| |
| put $ State o (exc:es) s
| |
| | |
| printT :: Output -> Eval EvalST ()
| |
| printT o = do st <- get
| |
| let s = getCount st
| |
| let e = getDebug st
| |
| let os = getIOS st
| |
| let out = show s ++ " - " ++ o
| |
| put $ State (out:os) e s
| |
| | |
| incTcounter :: Eval EvalST ()
| |
| incTcounter = do st <- get
| |
| let s = getCount st
| |
| let e = getDebug st
| |
| let o = getIOS st
| |
| put $ State o e (s+1)
| |
| | |
| evalT :: Term -> Eval EvalST Int
| |
| evalT (Con a) = do incTcounter
| |
| printT (formatLine (Con a) a)
| |
| return a
| |
| evalT (Add t u) = do a <- evalT t
| |
| b <- evalT u
| |
| incTcounter
| |
| let out = formatLine (Add t u) (a + b)
| |
| printT out
| |
| case (a+b) of
| |
| 42 -> do catchT "The Ultimate Answer Has Been Computed!! Now I'm tired!"
| |
| return (a+b)
| |
| 11 -> stopExecT "11.... I do not like this number!"
| |
| otherwise -> return (a + b)
| |
| | |
| | |
| formatLine :: Term -> Int -> Output
| |
| formatLine t a = "eval (" ++ show t ++ ") <= " ++ show a
| |
| | |
| printAll :: [String] -> IO ()
| |
| printAll [] = return ()
| |
| printAll (a:xs) = do putStrLn a
| |
| printAll xs
| |
| | |
| eval :: Term -> IO ()
| |
| eval exp = case execStateT (evalT exp) emptyState of
| |
| Fail e -> putStrLn e
| |
| Done (State a b c )
| |
| -> do printAll $ reverse a
| |
| putStrLn $ show $ unpackDone $
| |
| evalStateT (evalT exp) emptyState
| |
| case b of
| |
| [] -> putStrLn $ "Iterations: " ++ show c
| |
| _ -> do printAll $ reverse b
| |
| putStrLn $ "Iterations: " ++ show c
| |
| | |
| ---- testing functions ----
| |
| runEvalT :: Term -> String
| |
| runEvalT exp = case runStateT (evalT exp) emptyState of
| |
| Fail e -> e
| |
| Done (r,State o e s) -> "Result = " ++ show r ++
| |
| "; Iteration = " ++ show s ++
| |
| "; Output = " ++ show o ++
| |
| " - Exceptions = " ++ show e
| |
|
| |
| getEvalResult :: Term -> String
| |
| getEvalResult exp = case evalStateT (evalT exp) emptyState of
| |
| Fail e -> e
| |
| Done r -> "Result = " ++ show r
| |
| | |
| | |
| getSideEffects :: Term -> String
| |
| getSideEffects exp = case execStateT (evalT exp) emptyState of
| |
| Fail e -> e
| |
| Done (State o e s) -> "Iterations = " ++ show s ++
| |
| " - Output = " ++ show o ++
| |
| " - Exceptions = " ++ show e
| |
| | |
| {-
| |
| Some runs:
| |
| | |
| *MyStateT> eval (Add (Add (Add (Add (Con 40) (Con 2)) (Add (Con 12) (Con 30))) (Con 3)) (Con 10))
| |
| 1 - eval (Con 40) <= 40
| |
| 2 - eval (Con 2) <= 2
| |
| 3 - eval (Add (Con 40) (Con 2)) <= 42
| |
| 4 - eval (Con 12) <= 12
| |
| 5 - eval (Con 30) <= 30
| |
| 6 - eval (Add (Con 12) (Con 30)) <= 42
| |
| 7 - eval (Add (Add (Con 40) (Con 2)) (Add (Con 12) (Con 30))) <= 84
| |
| 8 - eval (Con 3) <= 3
| |
| 9 - eval (Add (Add (Add (Con 40) (Con 2)) (Add (Con 12) (Con 30))) (Con 3)) <= 87
| |
| 10 - eval (Con 10) <= 10
| |
| 11 - eval (Add (Add (Add (Add (Con 40) (Con 2)) (Add (Con 12) (Con 30))) (Con 3)) (Con 10)) <= 97
| |
| 97
| |
| Debug msg at Iteration 3: The Ultimate Answer Has Been Computed!! Now I'm tired!
| |
| Debug msg at Iteration 6: The Ultimate Answer Has Been Computed!! Now I'm tired!
| |
| Iterations: 11
| |
| *MyStateT>
| |
| | |
| *MyStateT> eval (Add (Add (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) (Add (Con 5) (Con 2))) (Con 2))
| |
| 1 - eval (Con 10) <= 10
| |
| 2 - eval (Con 2) <= 2
| |
| 3 - eval (Add (Con 10) (Con 2)) <= 12
| |
| 4 - eval (Con 12) <= 12
| |
| 5 - eval (Con 3) <= 3
| |
| 6 - eval (Add (Con 12) (Con 3)) <= 15
| |
| 7 - eval (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) <= 27
| |
| 8 - eval (Con 5) <= 5
| |
| 9 - eval (Con 2) <= 2
| |
| 10 - eval (Add (Con 5) (Con 2)) <= 7
| |
| 11 - eval (Add (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) (Add (Con 5) (Con 2))) <= 34
| |
| 12 - eval (Con 2) <= 2
| |
| 13 - eval (Add (Add (Add (Add (Con 10) (Con 2)) (Add (Con 12) (Con 3))) (Add (Con 5) (Con 2))) (Con 2)) <= 36
| |
| 36
| |
| Iterations: 13
| |
| *MyStateT>
| |
| | |
| *MyStateT> eval (Add (Con 5) (Con 6))
| |
| 11.... I do not like this number!
| |
| *MyStateT>
| |
| -}
| |
| </haskell>
| |
|
| |
|
| == Next?==
| | This probably makes sense for a functional programmer who is studying |
| We need a parser to get a string from input and turn into something of type Term!
| | Haskell for the first time. But, on the other side it will make the |
| | newcomer, who's not a functional programmer, believe that explaining |
| | monads in terms of "\" is just ugly, and definitely not Haskell. |
|
| |
|
| Let's see if we'll time for it... Fist we must complete the text above!!
| | This is my problem with Haskell: it hides complexity with |
| | constructions like "let...in", "where", "do". |
|
| |
|
| ==Suggested Readings==
| | Still I believe that if you want to use those constructions you must |
| | know what they do. And they do ugly stuff like the one you'll be |
| | looking at in this tutorial. |
|
| |
|
| Cale Gibbard, [http://haskell.org/haskellwiki/Monads_as_Containers Monads as Containers]
| | I am not saying that this is ''the'' way to learn Haskell. I'm just |
| | saying that this is the way I'm learning Haskell. And this is the way |
| | this tutorial has been written. |
|
| |
|
| Jeff Newbern, [http://www.nomaware.com/monads/html/index.html All About Monads]
| | ===Starting from the inside or the outside?=== |
|
| |
|
| [http://haskell.org/haskellwiki/IO_inside IO Inside]
| | In This tutorial I show monads from their inside. In "Meet Bob" I do |
| | the opposite. As I said I think (and I did it on purpose) that after |
| | reading "Meet Bob" you can have a general idea of what a monad is, but |
| | you need to go inside a monad to see how it works. |
|
| |
|
| [http://sigfpe.blogspot.com/2006/08/you-could-have-invented-monads-and.html You Could Have Invented Monads! (And Maybe You Already Have.) by sigfpe]
| | As a suggestion, I'd invite you to start with "Meet Bob", and then |
| | procede with the tutorial. |
|
| |
|
| | I hope the these two approaches will give you an overall image of a |
| | monad. |
|
| |
|
| ==Acknowledgments== | | ===Prerequisites=== |
|
| |
|
| Thanks to Neil Mitchell, Daniel Fisher, Bulat Ziganzhin, Brian Hulley
| | As I said, in order to understand this tutorial you need: |
| and Udo Stenzel for the invaluable help they gave, in the | | * a basic understanding of functional programming (this is required to understand Haskell after all) |
| [http://www.haskell.org/mailman/listinfo/haskell-cafe haskell-cafe mailing list],
| | * a basic understanding of the type system: |
| in understanding this topic.
| | ** how to create new types (with "data" and "newtype") |
| | ** how to use type constructors to construct and to match types and their internal components |
| | ** how to use a label field to retrieve a type internal component |
| | * a basic understanding of lambda abstraction |
|
| |
|
| I couldn't do it without their help. | | I hope I'll be able to write a short introductory summary to these |
| | topics (I will put it below this introductory remarks). |
|
| |
|
| Obviously errors are totally mine. But this is a wiki so, please,
| | Have fun with Haskell! |
| correct them!
| |
|
| |
|
| - [[User:AndreaRossato|AndreaRossato]] | | - [[User:AndreaRossato|Andrea Rossato]] |
|
| |
|
| [[Category:Tutorials]] | | [[Category:Tutorials]] |
| [[Category:Idioms]] | | [[Category:Idioms]] |
| | [[Category:Monad]] |