[Haskell-beginners] Re: Understanding Monadic I/O

Stephen Blackheath [to Haskell-Beginners] mutilating.cauliflowers.stephen at blacksapphire.com
Thu Jan 14 08:40:28 EST 2010


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
> <apfelmus at quantentunnel.de> 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 


More information about the Beginners mailing list