Understanding Monadic I/O

Hi, I'd like to understand in principle, how monadic I/O actions and combinators (>>=) are translated into imperative C--, to be executed sequentially. Does sequencing of IO actions mean nesting of C-- functions and passing values/state via additional function parameters? Is there any material with examples available? P.S.: Just to understand the magic better. I need it. BR -- Markus

Markus Böhm wrote:
Hi, I'd like to understand in principle, how monadic I/O actions and combinators (>>=) are translated into imperative C--, to be executed sequentially.
Does sequencing of IO actions mean nesting of C-- functions and passing values/state via additional function parameters?
Is there any material with examples available?
P.S.: Just to understand the magic better. I need it.
Well, the key point of the IO monad is of course that the internals are abstracted away. I'm not sure you will get much understanding out of them. If I am informed correctly, GHC represents IO as newtype IO a = IO ( World -> (# a, World #) ) But World is just a dummy type, it models the execution order as data dependencies so that the optimizer doesn't mess with it. In other word, World is stripped out completely, primitives like putChar are pretty much just compiled down to foreign function calls in C--. There are other possibilities, I believe NHC and YHC represent IO as newtype IO a = IO ( World -> a ) Again, the World argument is just a dummy. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Tx Heinrich. Could You explain how this "modelling the execution order as data dependency" works and how its tranlsated into sequential, imperative code? I mean in principle/for dummies.
From my beginner's perspective I feel I need that insight to understand how sustainable the abstraction is.
P.S.: Looking at forum discussions about simple, standard examples
like Fibonacci, arithmetic mean etc. I get the impression that the
naive, beautiful solution is evtl. not scalable (performance, memory)
and that it's necessary to understand the runtime behaviour underneath
the abstraction. Would You confirm that impression?
-- Markus
On Thu, Jan 14, 2010 at 10:36 AM, Heinrich Apfelmus
Markus Böhm wrote:
Hi, I'd like to understand in principle, how monadic I/O actions and combinators (>>=) are translated into imperative C--, to be executed sequentially.
Does sequencing of IO actions mean nesting of C-- functions and passing values/state via additional function parameters?
Is there any material with examples available?
P.S.: Just to understand the magic better. I need it.
Well, the key point of the IO monad is of course that the internals are abstracted away. I'm not sure you will get much understanding out of them.
If I am informed correctly, GHC represents IO as
newtype IO a = IO ( World -> (# a, World #) )
But World is just a dummy type, it models the execution order as data dependencies so that the optimizer doesn't mess with it. In other word, World is stripped out completely, primitives like putChar are pretty much just compiled down to foreign function calls in C--.
There are other possibilities, I believe NHC and YHC represent IO as
newtype IO a = IO ( World -> a )
Again, the World argument is just a dummy.
Regards, Heinrich Apfelmus
-- http://apfelmus.nfshost.com
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

P.S.: Looking at forum discussions about simple, standard examples like Fibonacci, arithmetic mean etc. I get the impression that the naive, beautiful solution is evtl. not scalable (performance, memory) and that it's necessary to understand the runtime behaviour underneath the abstraction. Would You confirm that impression?
-- Markus
If you're using the word 'naive' to mean what it normally means, isn't that basically truism? NAIVE IMPLEMENTATION IS NAIVE.

Markus, It isn't true that the naive, beautiful solution isn't scalable, but ultimately a Haskell programmer needs to understand 1. how lazy evaluation works, and 2. how IO and lazy evaluation interact. So I'll try to write a little bit on both, and hopefully answer your questions in the process. In my opinion, the price you pay for the power of lazy evaluation is a learning curve, and until you've mastered that learning curve, Haskell's space behaviour will be unpredictable. Once you've mastered it, it's predictable, but complex enough that even with perfect understanding it's possible to get it wrong. You can get very good at spotting space leaks, though, so even if you missed it at first, with experience you can usually find it quickly once you see it in the heap profile. However, Haskell - or at least GHC - does necessitate the use of the heap profiler from time to time. LAZY EVALUATION (AS IMPLEMENTED BY GHC) A value can either be a literal value, or it can be a thunk. For example, 1 + 1 is a thunk, and assuming the compiler hasn't optimized it, when it's demanded, the thunk is replaced in memory by a literal value '2', and the original thunk can be garbage collected. Now let's say we have a list 'let xs = [1..1000000]' which (due to previous IO) has become fully evaluated and therefore takes up memory. Later we get the expression 'length xs'. This is a thunk, and this thunk contains a reference to xs, thus preventing it being garbage collected. Its value is just an integer, but until it's evaluated, it takes up a large amount of space because of the reference to xs. This is an example of a space leak. Another example: 'length [1..1000000]' is a little different. It's a thunk (length ..) referring to a thunk ([1..1000000]). It takes up only a tiny bit of memory, since [1..1000000] is really just a recipe to create a list, not actually a list. The space behaviour of this expression is good, because [1..1000000] will be lazily created as 'length' consumes it, and the numbers are discarded as it goes. Now we come to constructors. A newtype has no effect on laziness, e.g. newtype MyNumber = MyNumber Int This is strict and exactly equivalent to an Int. However, constructors created with data, the list constructor : and tuples (x,y) are all lazy. Example: Normally foldl' is used for reducing a list down to a value, especially if it hasn't been evaluated yet. The ' means that it uses `seq` internally and prevents space leaks, e.g. foldl' (+) 0 [1..1000000] <-- good space behaviour When demanded, no space is wasted in evaluating this expression. However this... let pairs = [(x,y) | x <- [1..1000], y <- [1..1000]] in foldl' (\(x0,y0) (x1,y1) -> (x0 + x1, y0 + y1)) (0, 0) pairs ...has terrible space behaviour because of the (x,y) constructor. You end up with a nice strictly evaluated ( , ). However, it's only strict on the outside. The value is ( <vast chain of thunks>, <vast chain of thunks> ). To give it good space behaviour, you have to say foldl' (\(x0,y0) (x1,y1) -> let x = x0 + x1 y = y0 + y1 in x `seq` y `seq` (x,y)) (0, 0) pairs or alternatively foldl' (\(x0, y0) (x1, y1) -> let res = (x0 + x1, y0 + y1) in rnf res `seq` res) (0, 0) pairs or with {-# LANGUAGE BangPatterns #-} extension... foldl' (\(!x0, !y0) (x1, y1) -> (x0 + x1, y0 + y1)) (0, 0) pairs I know this is very difficult to deal with at first sight. "x `seq` y `seq` (x,y)" means "when this thunk is demanded, evaluate x and y, and then return (x,y) with these evaluated values". The 'let' binding for x and y are absolutely required to ensure you are forcing the same 'x' you are returning. It works because foldl' demands each intermediate result - but in this case only the ( , ) at the top level. We use `seq` to piggyback the evaluation of x and y onto the evaluation of the ( , ) constructor. HOW IO AND LAZINESS INTERACT The thing to grasp is that `seq` does NOT force evaluation - all it does is tie the evaluation of one thing to another. The runtime system is the only thing that forces evaluation, and it does it by forcing values of type IO a. It doesn't force the 'a' return value, only the IO action itself. So if you have an IO do block like this... let lenStr = show $ length [1..1000000] putStrLn lenStr ...then these are the steps that take place: 1. Make a thunk of type IO (), which refers to the expression 'print lenStr', and pass it to the runtime system (RTS). 2. The RTS demands the IO () value, and the mutator starts evaluating this thunk. 3. putStrLn has type String -> IO (), so the first thing we need to do is pass the thunk 'lenStr' to putStrLn. At some point in the process, lenStr is evaluated, and RTS gets its fully evaluated IO () value. 4. This IO () value represents some machine code, which the RTS then jumps to for the purpose of executing it. Whether it dereferences a pointer and jumps to the code it points at, or whether it's already laid out in memory as a 'jump' instruction, it doesn't matter. The latter, I think, but it's probably easier to visualize the former. Incidentally, GHC works by keeping track of a continuation context, rather than using a stack like C, which is why I said "jump" instead of "call". Anyway, it is *something like* this: load r0,=lenStr_thunk call evaluate call putStrLn If the IO action returns a value, then this value is a thunk as well. The RTS *only* evaluates IO actions - not return values - and unless something is needed as input to produce a value of IO a for the RTS, it does not get evaluated. To illustrate this process, it is possible to force evaluation like this: let x = _some_value_ y = _some_other_value_ x `seq` putStrLn y The result will be that x is guaranteed to be evaluated once the evaluated 'putStrLn y' is passed to the RTS. We have piggybacked the evaluation of x onto RTS's evaluation of an 'IO a' value. (This does not work for lazy monads like the state monad.) I hope that answers it without being too much information! Steve Markus Böhm wrote:
Tx Heinrich. Could You explain how this "modelling the execution order as data dependency" works and how its tranlsated into sequential, imperative code? I mean in principle/for dummies.
From my beginner's perspective I feel I need that insight to understand how sustainable the abstraction is.
P.S.: Looking at forum discussions about simple, standard examples like Fibonacci, arithmetic mean etc. I get the impression that the naive, beautiful solution is evtl. not scalable (performance, memory) and that it's necessary to understand the runtime behaviour underneath the abstraction. Would You confirm that impression?
-- Markus
On Thu, Jan 14, 2010 at 10:36 AM, Heinrich Apfelmus
wrote: Markus Böhm wrote:
Hi, I'd like to understand in principle, how monadic I/O actions and combinators (>>=) are translated into imperative C--, to be executed sequentially.
Does sequencing of IO actions mean nesting of C-- functions and passing values/state via additional function parameters?
Is there any material with examples available?
P.S.: Just to understand the magic better. I need it. Well, the key point of the IO monad is of course that the internals are abstracted away. I'm not sure you will get much understanding out of them.
If I am informed correctly, GHC represents IO as
newtype IO a = IO ( World -> (# a, World #) )
But World is just a dummy type, it models the execution order as data dependencies so that the optimizer doesn't mess with it. In other word, World is stripped out completely, primitives like putChar are pretty much just compiled down to foreign function calls in C--.
There are other possibilities, I believe NHC and YHC represent IO as
newtype IO a = IO ( World -> a )
Again, the World argument is just a dummy.
Regards, Heinrich Apfelmus
-- http://apfelmus.nfshost.com
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, Jan 14, 2010 at 7:40 AM, Stephen Blackheath [to
Haskell-Beginners]
I hope that answers it without being too much information!
That was actually a wonderful in-depth post. Is there somewhere (on the wiki, perhaps) that posts like these are (or could be) collected? I hate to think of them being "lost" in a mailing list archive rather than being available somewhere (perhaps labeled under an appropriate header, e.g.., "Understanding Lazy Evaluation"); it would be nice to have a series of posts written from various angles and authors to go over when banging one's head against a particular aspect of the language. :-)

Thank You very much for that enlighting post.
-- Markus
On Thu, Jan 14, 2010 at 3:37 PM, Tom Tobin
On Thu, Jan 14, 2010 at 7:40 AM, Stephen Blackheath [to Haskell-Beginners]
wrote: I hope that answers it without being too much information!
That was actually a wonderful in-depth post. Is there somewhere (on the wiki, perhaps) that posts like these are (or could be) collected? I hate to think of them being "lost" in a mailing list archive rather than being available somewhere (perhaps labeled under an appropriate header, e.g.., "Understanding Lazy Evaluation"); it would be nice to have a series of posts written from various angles and authors to go over when banging one's head against a particular aspect of the language. :-) _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Stephen Blackheath wrote:
LAZY EVALUATION (AS IMPLEMENTED BY GHC)
Thank you for this marvelous explanation! I do have a few comments, however, in particular concerning nomenclature and mental model.
A value can either be a literal value, or it can be a thunk. For example, 1 + 1 is a thunk, and assuming the compiler hasn't optimized it, when it's demanded, the thunk is replaced in memory by a literal value '2', and the original thunk can be garbage collected.
The standard nomenclature is *expression*, both 1 + 1 and 2 are expressions. The difference is that 2 is in *normal form*, whereas 1 + 1 is not fully evaluated yet. The standard model of evaluating expression in Haskell is called *graph reduction*, you can find some preliminary material in the wikibook http://en.wikibooks.org/wiki/Haskell/Graph_reduction "Thunk" traditionally refers to the machine representation of unevaluated expressions, usually as a pointer and usually in the context of discussing low level details like indirections and overwriting. I don't use the concept of "thunk" when reasoning about lazy evaluation because it has lots of unnecessary mental baggage, for example it must be a pointer that points to something. This is fine when discussing how GHC implements lazy evaluation, but it's not necessary when discussing how lazy evaluation itself works. Also, "thunk" doesn't distinguish between the different normal forms. In Haskell, the possible normal forms are *weak normal form* and *weak head normal form* (WHNF).
Now let's say we have a list 'let xs = [1..1000000]' which (due to previous IO) has become fully evaluated and therefore takes up memory. Later we get the expression 'length xs'. This is a thunk, and this thunk contains a reference to xs, thus preventing it being garbage collected. Its value is just an integer, but until it's evaluated, it takes up a large amount of space because of the reference to xs. This is an example of a space leak.
It is much clearer here to say that xs is the expression xs = 1 : 2 : 3 : 4 : 5 : ... : 1000000 : [] Clearly, this takes a lot of space to write down and so does n = length (1 : 2 : 3 : ... : 1000000 : []) Compare this to the expression [1..1000000] = enumFromTo 1 1000000 which takes just few bytes to write down. Of course, the normal form of n is 1000000 which does not take much space. Hence, it is desirable to evaluate n to WHNF as soon possible, unless it is completely unneeded.
Another example: 'length [1..1000000]' is a little different. It's a thunk (length ..) referring to a thunk ([1..1000000]). It takes up only a tiny bit of memory, since [1..1000000] is really just a recipe to create a list, not actually a list.
This is where the notion of "thunk" becomes unwieldy. The expression [1..1000000] is actually a list, just not in normal form.
The space behaviour of this expression is good, because [1..1000000] will be lazily created as 'length' consumes it, and the numbers are discarded as it goes.
It would be more precise to say that "the space usage while evaluating the expression to normal form is good".
Now we come to constructors. A newtype has no effect on laziness, e.g.
newtype MyNumber = MyNumber Int
This is strict and exactly equivalent to an Int. However, constructors created with data, the list constructor : and tuples (x,y) are all lazy.
The standard terminology is that data types are only evaluated to weak head normal form, i.e. only to the outermost constructor. Concerning newtypes, there is a subtle difference between a newtype newtype MyNumber = MyNumber Int and a data type with a strict field data MyNumber = MyNumber !Int Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Markus Böhm wrote:
Tx Heinrich. Could You explain how this "modelling the execution order as data dependency" works and how its tranlsated into sequential, imperative code? I mean in principle/for dummies.
From my beginner's perspective I feel I need that insight to understand how sustainable the abstraction is.
I don't know the details, but I think it's translated like this: putStrLn "Hello" >> putStrLn "World" => { state monad } \w1 -> let (a,w2) = primPutStrLn "Hello" w1 in primPutStrLn "World" w2 => { print out C code } a = cprimPutStrLn("Hello"); cprimPutStrLn("World"); The purpose of w1 and w2 is just to ensure that the first cprimPutStrLn is called before the second. Not very enlightening overall, if you ask me. It's not necessary to understand it anyway, the IO monad can be entirely understood as an algebraic data type, see for instance Swierstra und Altenkirch. Beauty in the beast. http://www.cse.chalmers.se/~wouter/Publications/BeautyInTheBeast.pdf Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Mon, Jan 11, 2010 at 2:57 PM, Markus Böhm
Hi, I'd like to understand in principle, how monadic I/O actions and combinators (>>=) are translated into imperative C--, to be executed sequentially.
Does sequencing of IO actions mean nesting of C-- functions and passing values/state via additional function parameters?
Is there any material with examples available?
Perhaps you could download JHC and compile with the -d c flag. It writes the C code, and JHC writes more understandable C code compared to GHC (IMHO) for example, main = putStrLn "hello, world" >> putStrLn "hello again, world" compiles to [lots of stuff] static void A_STD ftheMain(void) { jhc_function_inc(); fPrelude__IO__putStr(PROMOTE(c12)); (void)jhc_utf8_putchar((int)10); fPrelude__IO__putStr(PROMOTE(c23)); return (void)jhc_utf8_putchar((int)10); } so in this simple example you see there's no nesting of functions. David
participants (6)
-
David Virebayre
-
Heinrich Apfelmus
-
Markus Böhm
-
Martin Coxall
-
Stephen Blackheath [to Haskell-Beginners]
-
Tom Tobin