Difference between revisions of "IO inside"

From HaskellWiki
Jump to navigation Jump to search
m
m
Line 55: Line 55:
 
don't know anymore :) In order to understand how monads are used to
 
don't know anymore :) In order to understand how monads are used to
 
solve problem of I/O and side effects, you don't need to know it. It's
 
solve problem of I/O and side effects, you don't need to know it. It's
enough to just know elementary mathematics, like i does :)
+
enough to just know elementary mathematics, like I do :)
   
 
Let's imagine that we want to implement in Haskell well-known
 
Let's imagine that we want to implement in Haskell well-known

Revision as of 16:24, 30 June 2006

Haskell I/O always was a source of confusion and surprises for new Haskellers. While simple I/O code in Haskell looks very similar to it's equivalents in imperative languages, our attempts to write somewhat more complex often ended with total head mess. That is because Haskell I/O is really very different internally. Haskell is a pure language and even I/O system don't break this law.

The following text is an attempt to explain details of Haskell I/O implementation that should help you eventually master all the smart I/O tricks. Moreover, i added detailed explanation of various traps you can encounter on this way. After reading this text, you will get a degree "A Master of Haskell I/O" that is equal to Bachelor in CS and Mathematics, simultaneously :)

If you are new to Haskell I/O you may prefer to start with reading Introduction to IO page


Haskell is pure language

Haskell is pure language, which means that result of any function call is fully determined by its arguments. Pseudo-functions like rand() or getchar() in C which returns different results on each call, are just impossible and prohibited by language rules. Moreover, Haskell functions can't have side effects, i.e. they cannot make any changes in the "real world" - change files, write to the screen, print, send data over the network, and so on. These two restrictions together mean that any function call can be omitted, repeated, or replaced by the result of a previous call with the same parameters, and the language _guarantees_ that all these rearrangements will not change program result!

Let's compare this to C - compilers for this language just try to guess that function don't have side effects and it's result don't depends on some global variables. If this guess is wrong - the whole optimization becomes incorrect! As a consequence, C optimizers are enough conservative in their guesses and/or require from programmer to give them hints about usage (not meaning!) of functions and variables

Comparing to them, Haskell compiler is a set of pure mathematical transformations that can't be wrong by definition - they just translate one abstract data processing algorithm (i.e. some complex function) to another equivalent algorithm, just with better performance. This results in much better high-level optimization facilities comparing to C compilers

But this purity creates it's own problems. How we can do I/O, work with stateful algorithms and side effects in pure language? This question had many different solutions probed in 18 years of Haskell existence and finally one based on using monads was widely accepted


What is the monad?

What is the monad? It's something from mathematical category theory, i don't know anymore :) In order to understand how monads are used to solve problem of I/O and side effects, you don't need to know it. It's enough to just know elementary mathematics, like I do :)

Let's imagine that we want to implement in Haskell well-known 'getchar' function. What the type it should have? Let's try:

getchar :: Char

get2chars = [getchar,getchar]

What we will got with 'getchar' having just 'Char' type? You can see all the possible problems in 'get2chars' definition:

1) because Haskell compiler treats all functions as pure and not having side effects, it can avoid "excessive" call to 'getchar' and use one returned value two times

2) even if it will make two calls, there is no any clue to determine which call should be performed first. Are you want to return chars in the order they read, or in opposite order? Nothing in 'get2chars' definition answers this question.


How these problems can be solved, from plain programmer's viewpoint? Let's introduce fake parameter of 'getchar' to make each call "different" from compiler's POV:

getchar :: Int -> Char

get2chars = [getchar 1, getchar 2]

This right away solved the first problem mentioned above - now compiler will make two calls because it sees them as having different parameters. The whole 'get2chars' function should also had such fake parameter, otherwise we will have the same problem calling it:

getchar   :: Int -> Char
get2chars :: Int -> String

get2chars _ = [getchar 1, getchar 2]


Now, we need to give compiler some clue to determine which function it should call first. Haskell language don't provide any ways to express order of evaluation... except for data dependencies! How about adding artificial data dependency which prevents evaluation of second 'getchar' before the first one? In order to achieve this, we will return from 'getchar' additional fake result that will be used as parameter for next 'getchar' call:

getchar :: Int -> (Char, Int)

get2chars _ = [a,b]  where (a,i) = getchar 1
                           (b,_) = getchar i

So bad so good - now we can guarantee that 'a' is read before 'b' because 'b' reading need value (i) that is returned by 'a' reading!

We've added fake parameter to 'get2chars' but the problem is what Haskell compiler is too smart! It can believe that external 'getchar' function is really dependent on it's parameter but for 'get2chars' it will see that we just cheating and throw it away! Problem? How about passing this fake parameter to 'getchar' function?! In this case compiler can't guess that it really unused :)

get2chars i0 = [a,b]  where (a,i1) = getchar i0
                            (b,i2) = getchar i1


And more - 'get2chars' has all the same purity problems as 'getchar' function. If one need to call it two times, he need a way to describe order of these calls. Look at:

get4chars = [get2chars 1, get2chars 2]  -- order of `get2chars` calls isn't defined

We already know how to fight with such problem - 'get2chars' should also return some fake value that can be used to order calls:

get2chars :: Int -> (String, Int)

get4chars i0 = (a++b)  where (a,i1) = get2chars i0
                             (b,i2) = get2chars i1


But what the fake value it would return? If we will use some integer constant, too smart Haskell compiler will guess we are cheating, again :) What about returning the value returned by 'getchar'? See:

get2chars :: Int -> (String, Int)
get2chars i0 = ([a,b], i2)  where (a,i1) = getchar i0
                                  (b,i2) = getchar i1

Believe you or not, but we just constructed the whole "monadic" Haskell I/O system.


Welcome to RealWorld, baby :)

The 'main' Haskell function has the type:

main :: RealWorld -> ((), RealWorld)

where 'RealWorld' is faking type used instead of our Int. It is something like baton passed in relay-race. When 'main' calls some IO function, it pass the "RealWorld" it received as parameter. All IO functions has similar types involving RealWorld as parameter and result. To be exact, "IO" is a type synonym defined in the following way:

type IO a  =  RealWorld -> (a, RealWorld)

so. 'main' just has type "IO ()", 'getChar' has type "IO Char" and so on. Let's look at 'main' calling 'getChar' two times:

getChar :: RealWorld -> (Char, RealWorld)

main :: RealWorld -> ((), RealWorld)
main world0 = let (a, world1) = getChar world0
                  (b, world2) = getChar world1
              in ((), world2)


Look at this closely: 'main' passes to first 'getChar' the "world" it received. This 'getChar' returns some new value of type RealWorld, that is used in next call. Finally, 'main' returns the "world" it got from the second 'getChar':

1) Is it possible here to omit any call of 'getChar' if the char it read is not used? No, because we should return the "world" that is result of second 'getChar' and in turn requires "world" from first 'getChar'.

2) Is it possible to reorder 'getChar' calls? No, second 'getChar' can't be called before first one because it uses "world" it returns.

3) Is it possible to duplicate calls? In Haskell semantics - yes, but real compilers never duplicate work in such simple cases (otherwise, the programs generated will not have any speed guarantees)


As we already said, RealWorld values used like baton, passing them between all routines called by 'main' in strict order. Inside each routine called, RealWorld values used in the same way. In whole, in order to "compute" world to be returned from 'main', we should perform each IO procedure that is called from 'main', directly or indirectly. This means that each procedure inserted in the chain will be performed just at the moment (relative to other IO actions) when we planned it to be called. Let consider the following program:

main = do a <- ask "What is your name?"
          b <- ask "How old are you?"
          return ()

ask s = do putStr s
           readLn

Now you have enough knowledge to rewrite it in low-level way and check that each operation what should be performed, will be really performed with arguments it should have and in order we expecting


But what about conditional execution? No problem. Let's define the well-known 'when' operation:

when :: Bool -> IO () -> IO ()
when condition action world =
    if condition
      then action world
      else ((), world)

As you can see, we can easily include or exclude from execution chain IO procedures (actions) depending on the data values. If 'condition' will be False on call of 'when', 'action' will never be called because real Haskell compilers, again, never calls functions whose results don't required to calculate final result (i.e., here, final "world" value of 'main')

Loops and any more complex control structures can be implemented in the same way. Try it as an exercise!


Finally you may want to know how much costs this passing of RealWorld values all around. It's free! These fake values exist for compiler only while it analyze and optimize code, but when it goes to assembler code generation, it "suddenly" realize that this type is like "()", so all these parameters and result values can be omitted from generated code. Is it not really beautiful? :)


'>>=' and 'do' notation

All beginners (including me :) start by thinking that 'do' is some magic statement that executes IO actions. It's wrong - 'do' is just a syntax sugar that simplifies writing of IO procedures. 'do' notation is finally translated to the statements passing "world" values like we manually written above and need only to simplify gluing of several IO actions together. You don't require to use 'do' for just one statement:

  main = do putStr "Hello!"

is desugared just to:

  main = putStr "Hello!"

But nevertheless it's a Good Style to use 'do' even for one statement because it simplifies adding new statements in the future.


Let's examine how desugared 'do' with multiple statements on the following example:

main = do putStr "What is your name?"
          putStr "How old are you?"
          putStr "Nice day!"

'do' statement here just joins several IO actions that should be performed sequentially. It's translated to sequential applications of so named "binding operator", namely '>>':

main = (putStr "What is your name?")
       >> ( (putStr "How old are you?")
            >> (putStr "Nice day!")
          )

This binding operator just combines two IO actions, executing them sequentially by passing the "world" between them:

(>>) :: IO a -> IO b -> IO b
(action1 >> action2) world0 =
   let (a, world1) = action1 world0
       (b, world2) = action2 world1
   in (b, world2)

If such way to define operator looks strange for you, read this definition as the following:

action1 >> action2 = action
  where
    action world0 = let (a, world1) = action1 world0
                        (b, world2) = action2 world1
                    in (b, world2)

Now you can substitute definition of '>>' at the places of it's usage and check that program constructed by 'do' desugaring is actually the same as we can write by manually manipulating "world" values.


More complex example involves binding of variable using "<-":

main = do a <- readLn
          print a

This code is desugared into:

main = readLn
       >>= (\a -> print a)

As you should remember, '>>' binding operator silently ignores value of it's first action and returns as an overall result just result of second action. On the other side, '>>=' allows to use value of it's first action - it's passed as additional parameter to the second one! Look at the definition:

(>>=) :: IO a -> (a->IO b) -> IO b
(action1 >>= action2) world0 =
   let (a, world1) = action1 world0
       (b, world2) = action2 a world1
   in (b, world2)

First, what means type of second action, namely "a->IO b"? By substituting the "IO" definition, we get "a -> RealWorld -> (b, RealWorld)". This means that second action actually has two parameters - of type 'a' actually used inside it, and of type RealWorld used for sequencing of IO actions. That's a destiny - any IO procedure has one more parameter comparing to that you see in it's type signature. This parameter is hidden inside the definition of type alias "IO".

Second, you can use these '>>' and '>>=' operations to simplify your program. For example, in the code above we don't need to introduce the variable, because 'readLn' result can be send directly to 'print':

main = readLn >>= print


And third - as you see, the notation:

 do x <- action1
    action2

where 'action1' has type "IO a" and 'action2' has type "IO b", translated into:

 action1 >>= (\x -> action2)

where second argument of '>>=' has the type "a->IO b". It's the way how the "<-" binding processed - it just becomes parameter of subsequent operations represented as one large IO action. Look at the next example:

main = do putStr "What is your name?"
          a <- readLn
          putStr "How old are you?"
          b <- readLn
          print (a,b)

This code is desugared into:

main = putStr "What is your name?"
       >> readLn
       >>= \a -> putStr "How old are you?"
       >> readLn
       >>= \b -> print (a,b)

I omitted parentheses here, both '>>' and '>>=' operations are left-associative that leads to that 'a' and 'b' bindings introduced here is valid for all remaining actions. As an exercise, add the parentheses yourself and translate this procedure into the low-level code passing "world" values. I think it should be enough to finally realize how 'do' translation and binding operators work.


Oh, no. I forgot third monadic operator - 'return'. It just combines it's two parameters - value passed and "world":

return :: a -> IO a
return a world0  =  (a, world0)

How about translating some simple example of 'return' usage? Say,

main = do a <- readLn
          return (a*2)


Programmers with imperative languages background often thinks that 'return' in Haskell, like in other languages, immediately returns from the IO procedure. As you can see in its definition (and even just type!), such assumption is totally wrong. The only purpose of using 'return' is to "lift" some value (of type 'a') into the result of whole action (of type "IO a") and therefore it should be used only as last executed statements of some IO sequence. For example try to translate the following procedure into the low-level code:

main = do a <- readLn
          when (a>=0) $ do
              return ()
          print "a is negative"

and you will realize that 'print' statement is executed anyway. If you need to escape from middle of IO procedure, you can use the 'if' statement:

main = do a <- readLn
          if (a>=0)
            then return ()
            else print "a is negative"

Moreover, Haskell layout rules allow us to use the following layout:

main = do a <- readLn
          if (a>=0) then return ()
            else do
          print "a is negative"
          ...

that may be very useful for escaping from middle of longish 'do' statement.


Last exercise: implement function 'liftM' that lifts operations on plain values to the operations on monadic ones. It's type signature:

liftM :: (a->b) -> (IO a -> IO b)

If it's too hard for you, start with the following high-level definition and rewrite it in low-level fashion:

liftM f action = do x <- action
                    return (f x)


Mutable data (references, arrays, hash tables...)

As you should know, all names in Haskell are bind to one fixed value. This greatly simplify understanding of algorithms and optimization of code, but inappropriate for some cases. Yes, there a plenty of algorithms that is simpler to implement in terms of updatable variables, arrays and so on. This means that the value associated with variable, for example, can be different at different execution points, so reading it's value can't be considered as pure function. Imagine, for example the following code:

main = do let a0 = readVariable varA
              _  = writeVariable varA 1
              a1 = readVariable varA
          print (a0,a1)

Looks strange? First, two calls to 'readVariable' looks the same, so compiler can just reuse the value returned by first call. Second, result of 'writeVariable' call isn't used so compiler can (and will!) omit this call completely. To finish the picture, these 3 calls may be rearranged to any order because they looking independent on each other. What is the solution? You know - using of IO actions! IO actions guarantees us that:

  1. execution order will be retained
  2. each action will be mandatory executed
  3. result of the "same" action (such as "readVariable varA") will not be reused

So, the code above really should be written as:

main = do varA <- newIORef 0  -- Create and initialize new variable
          a0 <- readIORef varA
          writeIORef varA 1
          a1 <- readIORef varA
          print (a0,a1)

Here, 'varA' got type "IORef Int" which means "variable (reference) in IO monad holding value of type Int". newIORef creates new variable (reference) and returns it, and then read/write actions use this reference. Value returned by "readIORef varA" action may depend not only on variable involved but also on the moment of performing this operation so it can return different values on each call.

Arrays, hash tables and any other _mutable_ data structures are defined in the same way - there is operation that creates new "mutable value" and returns reference to it. Then special read and write operations in IO monad are used. The following example shows example of using mutable array:

 import Data.Array.IO
 main = do arr <- newArray (1,10) 37 :: IO (IOArray Int Int)
           a <- readArray arr 1
           writeArray arr 1 64
           b <- readArray arr 1
           print (a,b)

Here, array of 10 elements with 37 as initial values is created. After reading value of first element to 'a' this element's value is changed to 64 and then read again, to 'b'. As you can see by executing this code, 'a' will be set to 37 and 'b' to 64.


Other state-dependent operations are also often implemented as IO actions. For example, random numbers generator should return different values on each call. It looks natural to give it IO-involving type:

rand :: IO Int

Moreover, when you import C routines you should be careful - if this routine is impure, i.e. it's result depends on something in "real world" (file system, memory contents...), internal state and so on, you should give it IO-involving type. Otherwise, compiler can "optimize" repetitive calls of this procedure with the same parameters! :)

For example:

foreign import ccall
   sin :: Double -> Double

because 'sin' result depends only on it's argument, but

foreign import ccall
   tell :: Int -> IO Int

If you will declare 'tell' as pure function (without IO) then you may got the same position on each call! :)

IO actions as values

Now you should precisely understand why it's impossible to use IO actions inside non-IO (pure) procedures. Such procedures just don't get a "baton", don't know any "world" value to pass to IO action. RealWorld is abstract datatype, so they also can't construct it's values by himself, and it's a strict type, so 'undefined' also can't be used. So, prohibition of using IO actions inside pure procedures is just a type trick as it is usual in Haskell :)

But while pure code can't _execute_ IO actions, it can work with them as with any other functional values - they can be stored in data structures, passed as parameters and returned as results, collected in lists, and partially applied. But anyway IO action will remain functional value because we can't apply it to the last argument - of type RealWorld.

In order to _execute_ the IO action we need to apply it to some RealWorld value that can be done only inside some IO procedure, in it's "actions chain". And real execution of this action will take place only when this procedure is called as part of process of "calculating final value of world" for 'main'. Look at this example:

main = let get2chars = getChar >> getChar
           ((), world1) = putStr "Press two keys" world0
           (answer, world2) = get2chars world1
       in ((), world2)

Here we first bind value to 'get2chars' and then write binding involving 'putStr'. But what is an execution order? It is not defined by order of writing bindings, it is defined by order of processing "world" values! You can arbitrarily reorder binding statements - in any case execution order will be defined by dependence on passing "world" values. Let's see how this 'main' looks in the 'do' notation:

main = do let get2chars = getChar >> getChar
          putStr "Press two keys"
          get2chars
          return ()

As you can see, the 'let' binding that is not included in IO chain, is translated just to 'let' statement inside the 'do' sequence. And as you now should understand, placement of this 'let' don't has any impact on the evaluation order, which is defined by order of passing "world" values that is, in turn, defined by order of ordinal (non-let) statements inside 'do'!

Moreover, IO actions like this 'get2chars' can't be executed just because they are functions with RealWorld parameter. To execute them, we should supply the RealWorld parameter, i.e. insert them in 'main' chain, placing them in some 'do' sequence executed from 'main'. Until that is done, they will be keep as any function, in partially evaluated form. And we can work with IO actions as with any other functions - bind them to names (like above), save them to data structures, pass as function parameters and return as results - and they will not be performed until you give them this magic RealWorld parameter!

Let's try. How about defining list of IO actions?

ioActions :: [IO ()]
ioActions = [(print "Hello!"),
             (putStr "just kidding"),
             (getChar >> return ())
            ]

I used additional parentheses around each action, although they are not really required. If you still can't belive that these actions will not be executed until your command, just uncover this list type:

ioActions :: [RealWorld -> ((), RealWorld)]

Well, now we want to execute some of these actions. No problem, just insert them into the 'main' chain:

main = do head ioActions
          ioActions !! 1
          last ioActions

Looks strange, yeah? :) Really, any IO action you write in the 'do' statement (or use as parameter for '>>'/'>>=') is an expression returning result of type "IO a". Typically, you use some function that has type "x -> y -> ... -> IO a" and provide all these x, y and so on parameters. But you are not limited to this standard scenario - don't forget that Haskell is functional language and you are free to compute the functional value required (recall - "IO a" is a function type) in any possible way. Here we just extracted several functions from the list - no problem. This functional value can also be constructed on-the-fly, as we've done in previous example - it's also ok. Want to see this functional value passed as the parameter - heh, just look at the 'when' definition. Hey, we can sell, buy and rent these IO actions as any other functional values! For example, let's define function that executes all IO actions in the list:

sequence_ :: [IO a] -> IO ()
sequence_ [] = return ()
sequence_ (x:xs) = do x
                      sequence_ xs

No black magic - we just extracts IO actions from the list and inserts them into chain of IO operations that should be performed to "compute final world value" of entire 'sequence_' call.

With help of 'sequence_', we can rewrite our last 'main' as:

main = sequence ioActions


Haskell's ability to work with IO actions as with any other (functional or non-functional) value allows us to define control structures of any complexity. Try, for example, to define control structure that repeats the action until it returns the 'False' result:

while :: IO Bool -> IO ()
while action = ???


How about returning IO action as the function result? Well, we done this each time we defined IO procedure - they all return IO action that need RealWorld value to be performed. While we most times just executed them in chain of higher-level IO procedure, it's also possible to just collect them without actual execution:

main = do let a = sequence ioActions
              b = when True getChar
              c = getChar >> getChar
          putStr "'let' statements are not executed!"

These assigned IO procedures can be used as parameters to other procedures, or written to global variables, or processed in some other way, or just executed later, as we done in example with 'get2chars'.

But how about returning from IO procedure a parameterized IO action? Let's define a procedure that returns i'th byte from file represented as Handle:

readi h i = do hSeek h i AbsoluteSeek
               hGetChar h

So bad so good. But how about procedure that returns i'th byte of file with given name without reopening it each time?

readfilei :: String -> IO (Integer -> IO Char)
readfilei name = do h <- openFile name ReadMode
                    return (readi h)

As you can see, it's an IO procedure that opens file and returns... another IO procedure that will read byte specified. But we can go further and include 'readi' body into 'readfilei':

readfilei name = do h <- openFile name ReadMode
                    let readi h i = do hSeek h i AbsoluteSeek
                                       hGetChar h
                    return (readi h)

Good? May be better. Why we add 'h' as 'readi' parameter if it can be got from the environment where 'readi' now defined? Shorter will be:

readfilei name = do h <- openFile name ReadMode
                    let readi i = do hSeek h i AbsoluteSeek
                                     hGetChar h
                    return readi

What we've done here? We've build parameterized IO action involving local names inside 'readfilei' and returned it as the result. Now it can be used in following way:

main = do myfile <- readfilei "test"
          a <- myfile 0
          b <- myfile 1
          print (a,b)


Such usage of IO actions is very typical for Haskell programs - you just construct one or more (using tuple) IO actions that your need, with and/or without parameters, involving the parameters that your "constructor" received, and return them to caller. Then these IO actions can be used in rest of program without any knowledge about your internal implementation strategies. Actually, this is used to partially emulate OOP (to be exact, ADT) programming ideology.


For example, one of my program's modules is the memory suballocator. It receives address and size of large memory block and returns two procedures - one to allocate subblock of given size and second to return allocated block back:

memoryAllocator :: Ptr a -> Int -> IO (Int -> IO (Ptr b),
                                       Ptr c -> IO ())

memoryAllocator buf size = do ......
                              let alloc size = do ...
                                                  ...
                                  free ptr = do ...
                                                ...
                              return (alloc, free)

How this is implemented? 'alloc' and 'free' works with references created inside this procedure. Because creation of these references is a part of 'memoryAllocator' IO actions chain, new independent set of references will be created for each memory block for which 'memoryAllocator' is called:

memoryAllocator buf size = do start <- newIORef buf
                              end <- newIORef (buf `plusPtr` size)
                              ...

These two references (we will implement very simple memory allocator) are read and written in 'alloc' and 'free' definitions:

      let alloc size = do addr <- readIORef start
                          writeIORef start (addr `plusPtr` size)
                          return addr
                          
      let free ptr = do writeIORef start ptr

What we've defined here is just a pair of closures that is using state available on the moment of their definition. As you can see, it's as easy as in any other functional language, despite the Haskell's lack of direct support for non-pure functions.


unsafePerformIO and unsafeInterleaveIO

Programmers with imperative background often still looks for a ways to execute IO actions inside the pure procedures. But that this means? Imagine that you try to write procedure that reads contents of file with given name:

readContents :: Filename -> String

Defining it as pure function will simplify the code that use it, i agree. But this creates troubles for the compiler:

- first, this call is not inserted in sequence of "world transformations", so compiler don't get a hint - at what exact moment you want to execute this action. For example, if file contents is one at the program start and another at the end - what contents you want to see? Moment of "consumption" of this value don't make strong guarantees for execution order, because Haskell see all the functions as pure and fell free to reorder their execution as needed.

- second, attempts to read contents of file with the same name can be factorized despite the fact that file (or current directory) can be changed between calls. Again, Haskell looks at all the functions as pure ones and feel free to omit excessive calls with the same parameters.

So, implementing functions that interacts with Real World as pure ones considered as a Bad Behavior. Good boys never do it ;)


Nevertheless, there are (semi-official) ways to use IO actions inside of pure functions. As you should remember this is prohibited by requiring "baton" to call IO action. Pure function don't have the baton, but there is special procedure, that procures this baton from nowhere, uses it to call IO action and then throws resulting "world" away! A little low-level magic :) This very special procedure is:

unsafePerformIO :: IO a -> a

Let's look at it's (possible) definition:

unsafePerformIO :: (RealWorld -> (a,RealWorld)) -> a
unsafePerformIO action = let (a,world1) = action createNewWorld
                         in a

where 'createNewWorld' is internal function producing new value of RealWorld type.

Using unsafePerformIO, you can easily write pure functions that does I/O inside. But don't do this without real need, and remember to follow this rule: compiler don't know that you are cheating, it still consider each non-IO function as pure one. Therefore, all the usual optimization rules can (and will!) be applied to it's execution. So you must ensure that:

1) Result of each call depends only on it's arguments

2) You don't rely on side-effects of this function, which may be not executed if it's results are not used


Let's investigate this problem deeper. Function evaluation in Haskell are ruled by value's necessity - computed only the values that really required to calculate final result. But that this means according to 'main' function? To "calculate final world's" value, it's required to perform all the intermediate IO actions that included in 'main' chain. By using 'unsafePerformIO' we call IO actions outside of this chain. What can guarantee that they will be run? Nothing. The only case when they will be run is if that is required to compute overall function result (that in turn should be required to perform some action in 'main' chain). Here we return to the Haskell-natural evaluation-on-value-need. Now you should clearly see the difference:

- IO action inside IO procedure guaranteed to execute as long as it is inside 'main' chain - even when it's result is not used. You directly specify order of action's execution inside IO procedure. Data dependencies are simulated via "world" values.

- IO action inside 'unsafePerformIO' will be performed only if result of this operation is really used. Evaluation order is not guaranteed and you should not rely on it (except when you sure about data dependency).


I should also say that inside 'unsafePerformIO' call you can organize small internal chain of IO actions with help of the same binding operators and/or 'do' sugar:

one = unsafePerformIO $ do var <- newIORef 0
                           writeIORef var 1
                           readIORef var

and in this case ALL the operations in this chain will be performed as long as 'unsafePerformIO' result will be demanded. To ensure this, the actual 'unsafePerformIO' implementation evaluates "world" returned by the 'action':

unsafePerformIO action = let (a,world1) = action createNewWorld
                         in (world1 `seq` a)

('seq' operation strictly evaluates it's first argument before returning the value of second one)


But there is even more strange operation - 'unsafeInterleaveIO' that gets "official baton", makes it's piratical copy, and then run's "illegal" relay-race in parallel with main one! I can't further say about it's behavior without grief and indignation, it's not surprise that this operation is widely used in such software-piratical countries as Russia and China! ;) Don't even ask me - i will say nothing about this dirty trick i using permanently ;)


fixIO and 'mdo'

ST monad

Q monad

Welcome to machine: actual GHC implementation

A little disclaimer: after all, i should say that i don't described here what is a monad (i even don't know it myself) and what my explanations shows only the one _possible_ way to implement them in Haskell. For example, hbc Haskell compiler implements monads via continuations. I also don't said anything about exception handling that is natural part of "monad" concept. You can read "All about monads" guide to learn more on these topics.

But there are a good news: first, monad understanding you've build will work with any implementation. You just can't work with RealWorld values directly.

Second, IO monad implementation described here is really used in GHC, Hugs (nhc/jhc, too?) compilers. It is the really real IO definition from GHC sources:

newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))

It uses "State# RealWorld" type instead of our RealWorld, it uses "(# #)" strict tuple for optimization, and it adds IO data constructor around the type. Nevertheless, there are no principal changes. Knowing the principle of "chaining" IO actions via fake "state of world" values, now you can easily understand and write low-level implementations of GHC I/O operations.


The Yhc/nhc98 implementation

data World = World
newtype IO a = IO (World -> Either IOError a)

This implementation makes the "World" disappear somewhat, and returns Either a result "a", or if an error occurs then "IOError". The lack of the World on the right hand side of the function can only be done because the compiler knows special things about the IO type, and will not over optimise it.


Further reading

Look at the Books and tutorials#Using_Monads page

Are you have more questions? Ask in the haskell-cafe.