Difference between revisions of "IO inside"

From HaskellWiki
Jump to navigation Jump to search
m (Simple example of reusing previous result provided)
 
(112 intermediate revisions by 19 users not shown)
Line 1: Line 1:
Haskell I/O has always been a source of confusion and surprises for new Haskellers. While simple I/O code in Haskell looks very similar to its equivalents in imperative languages, attempts to write somewhat more complex code often result in a total mess. This is because Haskell I/O is really very different internally. Haskell is a pure language and even the I/O system can't break this purity.
+
''Haskell I/O can be a source of confusion and surprises for new Haskellers - if that's you, a good place to start is the [[Introduction to IO]] which can help you learn the basics (e.g. the syntax of I/O expressions) before continuing on.''
   
The following text is an attempt to explain the details of Haskell I/O implementations. This explanation should help you eventually master all the smart I/O tricks. Moreover, I've added a detailed explanation of various traps you might encounter along the way. After reading this text, you will receive a "Master of Haskell I/O" degree that is equal to a Bachelor in Computer Science and Mathematics, simultaneously :)
 
   
  +
If you are new to Haskell I/O you may prefer to start by reading the [[Introduction to IO]] page.
 
  +
While simple I/O code in Haskell looks very similar to its equivalents in imperative languages, attempts to write somewhat more complex code often result in a total mess. This is because Haskell I/O is really very different in how it actually works.
  +
  +
The following text is an attempt to explain the details of Haskell I/O implementations. This explanation should help you eventually learn all the smart I/O tips. Moreover, I've added a detailed explanation of various traps you might encounter along the way. After reading this text, you will be well on your way towards mastering I/O in Haskell.
   
   
 
== Haskell is a pure language ==
 
== Haskell is a pure language ==
   
Haskell is a pure language, which means that the result of any function call is fully determined by its arguments. Pseudo-functions like rand() or getchar() in C, which return different results on each call, are simply impossible to write in Haskell. Moreover, Haskell functions can't have side effects, which means that they can't effect any changes to the "real world", like changing files, writing to the screen, printing, sending data over the network, and so on. These two restrictions together mean that any function
+
Haskell is a pure language and even the I/O system can't break this purity. Being pure means that the result of any function call is fully determined by its arguments. Imperative routines like <code>rand()</code> or <code>getchar()</code> in C, which return different results on each call, are simply impossible to write in Haskell. Moreover, Haskell functions can't have side effects, which means that they can't make any changes "outside the Haskell program", like changing files, writing to the screen, printing, sending data over the network, and so on. These two restrictions together mean that any function call can be replaced by the result of a previous call with the same parameters, and the language ''guarantees'' that all these rearrangements will not change the program result! For example, the hyperbolic cosine function <code>cosh</code> can be defined in Haskell as:
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 the program result!
 
   
  +
<haskell>
Let's compare this to C: optimizing C compilers try to guess which functions have no side effects and don't depend on mutable global variables. If this guess is wrong, an optimization can change the program's semantics! To avoid this kind of disaster, C optimizers are conservative in their guesses or require hints from the programmer about the purity of functions.
 
  +
cosh r = (exp r + 1/exp r)/2
  +
</haskell>
  +
  +
using identical calls to <code>exp</code>, which is another function. So <code>cosh</code> can instead call <code>exp</code> once, and reuse the result:
  +
  +
<haskell>
  +
cosh r = (x + 1/x)/2 where x = exp r
  +
</haskell>
  +
  +
Let's compare this to C: optimizing C compilers try to guess which routines have no side effects and don't depend on mutable global variables. If this guess is wrong, an optimization can change the program's semantics! To avoid this kind of disaster, C optimizers are conservative in their guesses or require hints from the programmer about the purity of routines.
   
 
Compared to an optimizing C compiler, a Haskell compiler is a set of pure mathematical transformations. This results in much better high-level optimization facilities. Moreover, pure mathematical computations can be much more easily divided into several threads that may be executed in parallel, which is increasingly important in these days of multi-core CPUs. Finally, pure computations are less error-prone and easier to verify, which adds to Haskell's robustness and to the speed of program development using Haskell.
 
Compared to an optimizing C compiler, a Haskell compiler is a set of pure mathematical transformations. This results in much better high-level optimization facilities. Moreover, pure mathematical computations can be much more easily divided into several threads that may be executed in parallel, which is increasingly important in these days of multi-core CPUs. Finally, pure computations are less error-prone and easier to verify, which adds to Haskell's robustness and to the speed of program development using Haskell.
   
Haskell purity allows compiler to call only functions whose results
+
Haskell's purity allows the compiler to call only functions whose results are really required to calculate the final value of a top-level definition (e.g. <code>main</code>) - this is called lazy evaluation. It's a great thing for pure mathematical computations, but how about I/O actions? Something like
are really required to calculate final value of high-level function
 
(i.e., main) - this is called lazy evaluation. It's great thing for
 
pure mathematical computations, but how about I/O actions? Function
 
like (<hask>putStrLn "Press any key to begin formatting"</hask>) can't return any
 
meaningful result value, so how can we ensure that compiler will not
 
omit or reorder its execution? And in general: how we can work with
 
stateful algorithms and side effects in an entirely lazy language?
 
This question has had many different solutions proposed in 18 years of
 
Haskell development (see [[History of Haskell]]), though a solution based on '''''monads''''' is now
 
the standard.
 
   
  +
<haskell>
  +
putStrLn "Press any key to begin formatting"
  +
</haskell>
   
  +
can't return any meaningful result value, so how can we ensure that the compiler will not omit or reorder its execution? And in general: How we can work with stateful algorithms and side effects in an entirely lazy language? This question has had many different solutions proposed while Haskell was developed (see [[History of Haskell]]), with one solution eventually making its way into the current standard.
   
== What is a monad? ==
 
   
  +
== I/O in Haskell, simplified ==
What is a monad? It's something from mathematical category theory, which I
 
don't know anymore :) In order to understand how monads are used to
 
solve the 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 the well-known
+
Let's imagine that we want to implement the well-known <code>getchar</code> I/O operation in Haskell. What type should it have? Let's try:
'getchar' function. What type should it have? Let's try:
 
   
 
<haskell>
 
<haskell>
 
getchar :: Char
 
getchar :: Char
   
get2chars = [getchar,getchar]
+
get2chars :: String
  +
get2chars = [a, b] where a = getchar
  +
b = getchar
 
</haskell>
 
</haskell>
   
What will we get with 'getchar' having just the 'Char' type? You can see
+
What will we get with <code>getchar</code> having just the <code>Char</code> type? You can see one problem in the definition of <code>get2chars</code> immediately:
all the possible problems in the definition of 'get2chars':
 
   
# Because the Haskell compiler treats all functions as pure (not having side effects), it can avoid "excessive" calls to 'getchar' and use one returned value twice.
+
* because the Haskell compiler treats all definitions as pure (not having side effects), it can avoid "unnecessary" calls to <code>getchar</code> and use one returned value twice:
# Even if it does make two calls, there is no way to determine which call should be performed first. Do you want to return the two chars in the order in which they were read, or in the opposite order? Nothing in the definition of 'get2chars' answers this question.
 
   
  +
:<haskell>
How can these problems be solved, from the programmer's viewpoint?
 
  +
get2chars :: String
Let's introduce a fake parameter of 'getchar' to make each call
 
  +
get2chars = [x, x] where x = getchar -- this should be a legitimate optimisation!
"different" from the compiler's point of view:
 
  +
</haskell>
  +
  +
How can this problem be solved from the programmer's perspective? Let's introduce a fake parameter of <code>getchar</code> to make each call "different" from the compiler's point of view:
   
 
<haskell>
 
<haskell>
 
getchar :: Int -> Char
 
getchar :: Int -> Char
   
get2chars = [getchar 1, getchar 2]
+
get2chars :: String
  +
get2chars = [a, b] where a = getchar 1
  +
b = getchar 2
 
</haskell>
 
</haskell>
   
Right away, this solves the first problem mentioned above - now the
+
That solves the first problem mentioned above - now the compiler will make two calls because it sees that the calls have different parameters. So a single call to <code>getchar</code> should be even easier:
compiler will make two calls because it sees them as having different
 
parameters. The whole 'get2chars' function should also have a
 
fake parameter, otherwise we will have the same problem calling it:
 
   
 
<haskell>
 
<haskell>
  +
now_or_later :: String
getchar :: Int -> Char
 
  +
now_or_later = case getchar 0 of
get2chars :: Int -> String
 
  +
c | c == 'y' -> "Now"
  +
| c == 'Y' -> "Now"
  +
_ -> "Later"
  +
</haskell>
   
  +
...or not - depending on when the program is running (and how interested the user is :-) <span style="white-space: nowrap"><code>getchar 0</code></span> could equal:
get2chars _ = [getchar 1, getchar 2]
 
  +
* <code>'y'</code>
  +
* <code>'Y'</code>
  +
* or some other character: ''ouch!''
  +
  +
=== A matter of time ===
  +
  +
The problem is that while <code>getchar</code> looks like a function, it breaks one of the rules of being a function:
  +
* if a function's result changes, it '''should be''' because it's arguments have changed.
  +
  +
Instead of arbitrary <code>Int</code> values, what about using a ever-changing quantity as the input to <code>getchar</code>...like time? We just need to modify <code>get2chars</code> and <code>now_or_later</code> accordingly:
  +
  +
<haskell>
  +
getchar :: Time -> Char
  +
  +
get2chars :: (Time, Time) -> String
  +
get2chars (t1, t2) = [a, b] where a = getchar t1
  +
b = getchar t2
  +
  +
now_or_later :: Time -> String
  +
now_or_later t = case getchar t of
  +
c | c == 'y' -> "Now"
  +
| c == 'Y' -> "Now"
  +
_ -> "Later"
 
</haskell>
 
</haskell>
   
  +
Now the result of calling <code>getchar</code> is free to change along with its input, irrespective of when the user runs the program.
   
  +
=== Time after time ===
Now we need to give the compiler some clue to determine which function it
 
  +
should call first. The Haskell language doesn't provide any way to express
 
  +
Unlike <code>getchar</code> and <code>now_or_later</code>, calling <code>get2chars</code> is somewhat annoying - it requires a pair of <code>Time</code> values, which presents a new problem. If <code>t1</code> is less than <code>t2</code>, then:
order of evaluation... except for data dependencies! How about adding an
 
  +
artificial data dependency which prevents evaluation of the second
 
  +
* should <code>get2chars (t1, t2) == reverse (get2chars (t2, t1))</code>?
'getchar' before the first one? In order to achieve this, we will
 
  +
* or should <code>get2chars (t2, t1)</code> be invalid?
return an additional fake result from 'getchar' that will be used as a
 
  +
parameter for the next 'getchar' call:
 
  +
We can't just "snap" <code>Time</code> values into two "pieces", one for each <code>getchar</code> call:
   
 
<haskell>
 
<haskell>
getchar :: Int -> (Char, Int)
+
timeSnaps :: Time -> (Time, Time) -- ?!
  +
</haskell>
   
  +
so we'll just arrange for <code>getchar</code> to return its "completion time" along with the received input character:
get2chars _ = [a,b] where (a,i) = getchar 1
 
  +
(b,_) = getchar i
 
  +
<haskell>
  +
getchar :: {- starting -} Time -> (Char, {- completion -} Time)
  +
  +
now_or_later :: Time -> String
  +
now_or_later t1 = case getchar t1 of
  +
(c, _) | c == 'y' -> "Now"
  +
| c == 'Y' -> "Now"
  +
_ -> "Later
 
</haskell>
 
</haskell>
   
  +
That "completion time" can then be used as the "starting time" for another <code>getchar</code> call:
So far so good - now we can guarantee that 'a' is read before 'b'
 
because reading 'b' needs the value ('i') that is returned by reading 'a'!
 
   
  +
<haskell>
We've added a fake parameter to 'get2chars' but the problem is that the
 
  +
get2chars :: Time -> String
Haskell compiler is too smart! It can believe that the external 'getchar'
 
  +
get2chars t1 = [a, b] where (a, t2) = getchar t1
function is really dependent on its parameter but for 'get2chars' it
 
  +
(b, _) = getchar t2
will see that we're just cheating because we throw it away! Therefore it won't feel obliged to execute the calls in the order we want. How can we fix this? How about passing this fake parameter to the 'getchar' function?! In this case
 
  +
</haskell>
the compiler can't guess that it is really unused :)
 
  +
  +
with the added benefit of ordering those calls...but not calls to <code>get2chars</code> or <code>now_or_later</code>. Fortunately, this is simple to resolve - from now on, all of our I/O definitions will have "completion times":
   
 
<haskell>
 
<haskell>
  +
getchar :: Time -> (Char, Time)
get2chars i0 = [a,b] where (a,i1) = getchar i0
 
  +
(b,i2) = getchar i1
 
  +
get2chars :: Time -> (String, Time)
  +
get2chars t1 = ([a, b], t3) where (a, t2) = getchar t1
  +
(b, t3) = getchar t2
  +
  +
now_or_later :: Time -> (String, Time)
  +
now_or_later t1 = case getchar t1 of
  +
(c, t2) | c == 'y' -> ("Now", t2)
  +
| c == 'Y' -> ("Now", t2)
  +
| otherwise -> ("Later", t2)
 
</haskell>
 
</haskell>
   
  +
==== The fun of plumbing ====
   
  +
Solving one problem now leads to another:
And more - 'get2chars' has all the same purity problems as the 'getchar'
 
function. If you need to call it two times, you need a way to describe
 
the order of these calls. Look at:
 
   
 
<haskell>
 
<haskell>
  +
get2chars :: Time -> (String, Time)
get4chars = [get2chars 1, get2chars 2] -- order of 'get2chars' calls isn't defined
 
  +
get2chars t1 = ([a, b], t3) where (a, t2) = getchar t3 -- this might take
  +
(b, t3) = getchar t2 -- a while...
 
</haskell>
 
</haskell>
   
  +
The cause of both problems is the same: the manual manoveuring of those extra intermediate values between the definitions which use them. We need some way to automate this tedium...
We already know how to deal with these problems - 'get2chars' should
 
  +
also return some fake value that can be used to order calls:
 
  +
=== Enter the monad ===
  +
  +
But what is a monad? For Haskell, it's a three-way partnership between:
  +
* a type: <code>M a</code>
  +
* an operator <code>unit(M) :: a -> M a</code>
  +
* an operator <code>bind(M) :: M a -> (a -> M b) -> M b</code>
  +
  +
where <code>unit(M)</code> and <code>bind(M)</code> satisfy the [[monad laws]].
  +
  +
As an actual Haskell declaration:
  +
  +
<haskell>
  +
class Monad m where
  +
return :: a -> m a -- "unit"
  +
(>>=) :: m a -> (a -> m b) -> m b -- "bind"
  +
</haskell>
  +
  +
So how does something so <strike>vague</strike> abstract help us with I/O? Because this abstraction allows us to hide the manipulation of those irksome intermediate values! We start by modifying <code>get2chars</code> and <code>now_or_later</code> to make the use of intermediate values more visible:
   
 
<haskell>
 
<haskell>
get2chars :: Int -> (String, Int)
+
get2chars = \t1 -> let (a, t2) = getchar t1 in
  +
let (b, t3) = getchar t2 in
  +
let r = [a, b] in
  +
(r, t3)
   
get4chars i0 = (a++b) where (a,i1) = get2chars i0
+
now_or_later = \t1 -> let (c, t2) = getchar t1 in
(b,i2) = get2chars i1
+
let r = if elem c "yY" then "Now" else "Later" in
  +
(r, t2)
 
</haskell>
 
</haskell>
   
  +
With a suitable type:
   
  +
<haskell>
But what's the fake value 'get2chars' should return? If we use some integer constant, the excessively-smart Haskell compiler will guess that we're cheating again :) What about returning the value returned by 'getchar'? See:
 
  +
data IO a = Act (Time -> (a, Time))
  +
  +
getchar :: IO Char
  +
</haskell>
  +
  +
and an appropriate <code>Monad</code> instance:
   
 
<haskell>
 
<haskell>
  +
instance Monad IO where
get2chars :: Int -> (String, Int)
 
get2chars i0 = ([a,b], i2) where (a,i1) = getchar i0
+
m >>= k = let actual (Act m) = m in
(b,i2) = getchar i1
+
Act $ \t1 -> case actual m t1 of (x, t2) -> actual (k x) t2
  +
return x = Act $ \t1 -> (x, t1)
 
</haskell>
 
</haskell>
   
  +
we can define <code>get2chars</code> and <code>now_or_later</code> using the <code>Monad</code> methods:
Believe it or not, but we've just constructed the whole "monadic"
 
Haskell I/O system.
 
   
  +
<haskell>
  +
get2chars :: IO String
  +
get2chars = getchar >>= \a ->
  +
getchar >>= \b ->
  +
return [a, b]
   
  +
now_or_later :: IO String
  +
now_or_later = getchar >>= \c ->
  +
return (if elem c "yY" then "Now" else "Later")
  +
</haskell>
   
  +
No more manually <strike>mangling</strike> managing intermediate values! We just need to be sure that our chosen I/O operations - <code>getchar</code> and the the <code>Monad</code> methods - use them correctly. This allows <code>IO</code> to be made into an <i>abstract data type</i>:
== Welcome to the RealWorld, baby :) ==
 
   
  +
<haskell>
The 'main' Haskell function has the type:
 
  +
data IO
  +
getchar :: IO Char
  +
return :: a -> IO a
  +
(>>=) :: IO a -> (a -> IO b) -> IO b
  +
</haskell>
  +
  +
Now only the Haskell implementation (e.g. compilers like ghc or jhc) needs to know how I/O actions actually work.
  +
  +
So there you have it - a miniature monadic I/O system in Haskell!
  +
  +
=== Beyond time ===
  +
  +
We could define <code>Time</code> as a regular Haskell type:
   
 
<haskell>
 
<haskell>
  +
data Time = Now Double
main :: RealWorld -> ((), RealWorld)
 
 
</haskell>
 
</haskell>
   
  +
However we've been conveniently ignoring some other details:
where 'RealWorld' is a fake type used instead of our Int. It's something
 
  +
like the baton passed in a relay race. When 'main' calls some IO function,
 
  +
* For simplicity, we've only dealt with one primitive I/O action in our miniature I/O system - <span style="white-space: nowrap"><code>getchar :: IO Char</code></span>. Clearly there's more to I/O than just reading in characters!
it passes the "RealWorld" it received as a parameter. All IO functions have
 
  +
similar types involving RealWorld as a parameter and result. To be
 
  +
* Programs can have more than one user:
exact, "IO" is a type synonym defined in the following way:
 
  +
:* If one presses <code>'y'</code>,
  +
:* another presses <code>'n'</code>,
  +
:* the rest press the space bar: <code> </code>,
  +
:at exactly the same time - what should the result of <code>getchar</code> be equal to then?
  +
  +
:We could try to avoid that problem by measuring time down to the nearest millisecond, microsecond, nanosecond, etc - however, these days humans aren't the only users: a program can also use another program. It's happening right now in the operating system running on your computer.
  +
  +
  +
  +
So what should replace those <code>Time</code> values? It would be futile to try defining a regular Haskell type which can work <i>for all possible outside interactions</i>. So the only practical choice is to use another abstract type:
   
 
<haskell>
 
<haskell>
type IO a = RealWorld -> (a, RealWorld)
+
data RealWorld
  +
  +
newtype IO a = Act (RealWorld -> (a, RealWorld))
  +
</haskell>
  +
  +
  +
== Running with the <code>RealWorld</code> ==
  +
  +
Warning: The following story about I/O is incorrect in that it cannot actually explain some important aspects of I/O (including interaction and concurrency). However, some people find it useful to begin developing an understanding.
  +
  +
From our definition of the <code>IO</code> type, we can see that the <code>RealWorld</code> is used like the baton passed in a relay race. When an I/O action is called, it passes the <code>RealWorld</code> it received as a parameter. All I/O actions have similar types involving <code>RealWorld</code> as a parameter and result.
  +
  +
So, <code>main</code> just has type <code>IO ()</code>, <code>getChar</code> has type <span style="white-space: nowrap"><code>IO Char</code></span> and so on. You can think of the type <span style="white-space: nowrap"><code>IO Char</code></span> as meaning "take the current <code>RealWorld</code>, do something to it, and return a <code>Char</code> and a (possibly changed) <code>RealWorld</code>". Let's look at <code>main</code> calling <code>getChar</code> two times:
  +
  +
<haskell>
  +
getChar :: IO Char
  +
  +
main :: IO ()
  +
main = getChar >>= \a ->
  +
getChar >>= \b ->
  +
return ()
 
</haskell>
 
</haskell>
   
  +
Remember how we changed the <code>IO</code> type to use a <code>newtype</code> declaration? That decision now allows us to rewrite <code>main</code> as:
So, 'main' just has type "IO ()", 'getChar' has type "IO Char" and so
 
on. You can think of the type "IO Char" as meaning "take the current RealWorld, do something to it, and return a Char and a (possibly changed) RealWorld". Let's look at 'main' calling 'getChar' two times:
 
   
 
<haskell>
 
<haskell>
Line 166: Line 297:
 
</haskell>
 
</haskell>
   
  +
Look at this closely: <code>main</code> passes the "world" it received to the first <code>getChar</code>. This <code>getChar</code> returns some new value of type <code>RealWorld</code> that gets used in the next call. Finally, <code>main</code> returns the "world" it got from the second <code>getChar</code>.
   
  +
* Is it possible here to omit any call of <code>getChar</code> if the <code>Char</code> it read is not used? No: we need to return the "world" that is the result of the second <code>getChar</code> and this in turn requires the "world" returned from the first <code>getChar</code>.
Look at this closely: 'main' passes to first 'getChar' the "world" it
 
received. This 'getChar' returns some new value of type RealWorld
 
that gets used in the next call. Finally, 'main' returns the "world" it got
 
from the second 'getChar'.
 
   
# Is it possible here to omit any call of 'getChar' if the Char it read is not used? No, because we need to return the "world" that is the result of the second 'getChar' and this in turn requires the "world" returned from the first 'getChar'.
+
* Is it possible to reorder the <code>getChar</code> calls? No: the second <code>getChar</code> can't be called before the first one because it uses the "world" returned from the first call.
# Is it possible to reorder the 'getChar' calls? No: the second 'getChar' can't be called before the first one because it uses the "world" returned from the first call.
 
# 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).
 
   
  +
* 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, <code>RealWorld</code> values are used like a baton which gets passed between all actions called by <code>main</code> in strict order. Inside each action called, <code>RealWorld</code> values are used in the same way. Overall, in order to "compute" the world to be returned from <code>main</code>, we should perform each I/O action that is called from <code>main</code>, directly or indirectly. This means that each action inserted in the chain will be performed just at the moment (relative to the other I/O actions) when we intended it to be called. Let's consider the following program:
As we already said, RealWorld values are used like a baton which gets passed
 
between all routines called by 'main' in strict order. Inside each
 
routine called, RealWorld values are used in the same way. Overall, in
 
order to "compute" the 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 the other IO actions) when we intended it
 
to be called. Let's consider the following program:
 
   
 
<haskell>
 
<haskell>
Line 195: Line 316:
 
</haskell>
 
</haskell>
   
Now you have enough knowledge to rewrite it in a low-level way and
+
Now you have enough knowledge to rewrite it in a low-level way and check that each operation that should be performed will really be performed with the arguments it should have and in the order we expect.
check that each operation that should be performed will really be
 
performed with the arguments it should have and in the order we expect.
 
   
  +
But what about conditional execution? No problem. Let's define the well-known <code>when</code> operation:
 
But what about conditional execution? No problem. Let's define the
 
well-known 'when' operation:
 
   
 
<haskell>
 
<haskell>
 
when :: Bool -> IO () -> IO ()
 
when :: Bool -> IO () -> IO ()
  +
when condition action =
  +
if condition
  +
then action
  +
else return ()
  +
</haskell>
  +
  +
Now to simplify it:
  +
  +
<haskell>
 
when condition action world =
 
when condition action world =
 
if condition
 
if condition
Line 211: Line 337:
 
</haskell>
 
</haskell>
   
  +
As you can see, we can easily include or exclude from the execution chain I/O actions depending on the data values. If <code>condition</code> will be <code>False</code> on the call of <code>when</code>, <code>action</code> will never be called because real Haskell compilers, again, never call functions whose results are not required to calculate the final result (''i.e.'' here, the final "world" value of <code>main</code>).
As you can see, we can easily include or exclude from the execution chain
 
IO procedures (actions) depending on the data values. If 'condition'
 
will be False on the call of 'when', 'action' will never be called because
 
real Haskell compilers, again, never call functions whose results
 
are not required to calculate the final result (''i.e.'', here, the final "world" value of 'main').
 
   
Loops and more complex control structures can be implemented in
+
Loops and more complex control structures can be implemented in the same way. Try it as an exercise!
the same way. Try it as an exercise!
 
   
  +
Finally, you may want to know how much passing these <code>RealWorld</code> values around the program costs. It's free! These fake values exist solely for the compiler while it analyzes and optimizes the code, but when it gets to assembly code generation, it notices that <code>RealWorld</code> is like <code>()</code> - it contains no actual information - so all those <code>RealWorld</code> parameters and result values can be omitted from the final generated code: they're not needed any more!
   
Finally, you may want to know how much passing these RealWorld
 
values around the program costs. It's free! These fake values exist solely for the compiler while it analyzes and optimizes the code, but when it gets to assembly code generation, it "suddenly" realize that this type is like "()", so
 
all these parameters and result values can be omitted from the final generated code. Isn't it beautiful? :)
 
   
  +
== <code>(>>=)</code> and <code>do</code> notation ==
   
  +
All beginners (including me) start by thinking that <code>do</code> is some super-awesome statement that executes I/O actions. That's wrong - <code>do</code> is just syntactic sugar that simplifies the writing of definitions that use I/O (and also other monads, but that's beyond the scope of this tutorial). <code>do</code> notation eventually gets translated to a series of I/O actions passing "world" values around like we've manually written above. This simplifies the gluing of several I/O actions together. You don't need to use <code>do</code> for just one action; for example,
 
== '>>=' and 'do' notation ==
 
 
All beginners (including me :)) start by thinking that 'do' is some
 
magic statement that executes IO actions. That's wrong - 'do' is just
 
syntactic sugar that simplifies the writing of procedures that use IO (and also other monads, but that's beyond the scope of this tutorial). 'do' notation eventually gets translated to statements passing "world" values around like we've manually written above and is used to simplify the gluing of several
 
IO actions together. You don't need to use 'do' for just one statement; for instance,
 
   
 
<haskell>
 
<haskell>
main = do putStr "Hello!"
+
main = do putStr "Hello!"
 
</haskell>
 
</haskell>
  +
 
 
is desugared to:
 
is desugared to:
   
 
<haskell>
 
<haskell>
main = putStr "Hello!"
+
main = putStr "Hello!"
 
</haskell>
 
</haskell>
   
  +
Let's examine how to desugar a <code>do</code>-expression with multiple actions in the following example:
But nevertheless it's considered Good Style to use 'do' even for one statement
 
because it simplifies adding new statements in the future.
 
 
 
Let's examine how to desugar a 'do' with multiple statements in the
 
following example:
 
   
 
<haskell>
 
<haskell>
Line 257: Line 366:
 
</haskell>
 
</haskell>
   
The 'do' statement here just joins several IO actions that should be
+
The <code>do</code>-expression here just joins several I/O actions that should be performed sequentially. It's translated to sequential applications of one of the so-called "binding operators", namely <code>(>>)</code>:
performed sequentially. It's translated to sequential applications
 
of one of the so-called "binding operators", namely '>>':
 
   
 
<haskell>
 
<haskell>
Line 268: Line 375:
 
</haskell>
 
</haskell>
   
  +
Defining <code>(>>)</code> looks easy:
This binding operator just combines two IO actions, executing them
 
sequentially by passing the "world" between them:
 
   
 
<haskell>
 
<haskell>
 
(>>) :: IO a -> IO b -> IO b
 
(>>) :: IO a -> IO b -> IO b
  +
action1 >> action2 = action1 >>= \_ -> action2
  +
</haskell>
  +
  +
But if we simplify this binding operator, we can see it combining its two I/O actions, executing them sequentially by passing the "world" between them:
  +
  +
<haskell>
 
(action1 >> action2) world0 =
 
(action1 >> action2) world0 =
let (a, world1) = action1 world0
+
let (a, world1) = action1 world0 -- note: a not used
 
(b, world2) = action2 world1
 
(b, world2) = action2 world1
 
in (b, world2)
 
in (b, world2)
 
</haskell>
 
</haskell>
   
If defining operators this way looks strange to you, read this
+
If defining operators this way looks strange to you, read this definition as follows:
  +
definition as follows:
 
 
 
<haskell>
 
<haskell>
 
action1 >> action2 = action
 
action1 >> action2 = action
Line 290: Line 401:
 
</haskell>
 
</haskell>
   
Now you can substitute the definition of '>>' at the places of its usage
+
Now you can substitute the definition of <code>(>>)</code> at the places of its usage and check that program constructed by the <code>do</code> desugaring is actually the same as we could write by manually manipulating "world" values.
and check that program constructed by the 'do' desugaring is actually the
 
same as we could write by manually manipulating "world" values.
 
   
  +
A more complex example involves the binding of variables using <code><-</code>:
 
A more complex example involves the binding of variables using "<-":
 
   
 
<haskell>
 
<haskell>
Line 309: Line 417:
 
</haskell>
 
</haskell>
   
  +
where <code>(>>=)</code> corresponds to the <code>bind</code> operation in our miniature I/O system.
As you should remember, the '>>' binding operator silently ignores
 
  +
the value of its first action and returns as an overall result
 
the result of its second action only. On the other hand, the '>>=' binding operator (note the extra '=' at the end) allows us to use the result of its first action - it gets passed as an additional parameter to the second one! Look at the definition:
+
As you should remember, the <code>(>>)</code> binding operator silently ignores the value of its first action and returns as an overall result the result of its second action only. On the other hand, the <code>(>>=)</code> binding operator (note the extra <code>=</code> at the end) allows us to use the result of its first action - it gets passed as an additional parameter to the second one! Let's simplify its definition:
   
 
<haskell>
 
<haskell>
  +
(action >>= reaction) world0 =
(>>=) :: IO a -> (a -> IO b) -> IO b
 
(action1 >>= action2) world0 =
+
let (a, world1) = action world0
let (a, world1) = action1 world0
+
(b, world2) = reaction a world1
(b, world2) = action2 a world1
 
 
in (b, world2)
 
in (b, world2)
 
</haskell>
 
</haskell>
   
  +
* What does the type of <code>reaction</code> - namely <span style="white-space: nowrap"><code>a -> IO b</code></span> - mean? By substituting the <code>IO</code> definition, we get <span style="white-space: nowrap"><code>a -> RealWorld -> (b, RealWorld)</code></span>. This means that <code>reaction</code> actually has two parameters - the type <code>a</code> actually used inside it, and the value of type <code>RealWorld</code> used for sequencing of I/O actions. That's always the case - any I/O definition has one more parameter compared to what you see in its type signature. This parameter is hidden inside the definition of the <code>IO</code> type:
First, what does the type of the second "action" (more precisely, a function which returns an IO action), namely "a -> IO b", mean? By
 
substituting the "IO" definition, we get "a -> RealWorld -> (b, RealWorld)".
 
This means that second action actually has two parameters
 
- the type 'a' actually used inside it, and the value of type RealWorld used for sequencing of IO actions. That's always the case - any IO procedure has one
 
more parameter compared to what you see in its type signature. This
 
parameter is hidden inside the definition of the type alias "IO".
 
   
  +
:<haskell>
Second, you can use these '>>' and '>>=' operations to simplify your
 
  +
newtype IO a = Act (RealWorld -> (a, RealWorld))
program. For example, in the code above we don't need to introduce the
 
  +
</haskell>
variable, because the result of 'readLn' can be send directly to 'print':
 
   
  +
* You can use these <code>(>>)</code> and <code>(>>=)</code> operations to simplify your program. For example, in the code above we don't need to introduce the variable, because the result of <code>readLn</code> can be send directly to <code>print</code>:
<haskell>
 
  +
  +
:<haskell>
 
main = readLn >>= print
 
main = readLn >>= print
 
</haskell>
 
</haskell>
   
  +
As you see, the notation:
 
And third - as you see, the notation:
 
   
 
<haskell>
 
<haskell>
Line 344: Line 447:
 
</haskell>
 
</haskell>
   
where 'action1' has type "IO a" and 'action2' has type "IO b",
+
where <code>action1</code> has type <code>IO a</code> and <code>action2</code> has type <span style="white-space: nowrap"><code>IO b</code></span>, translates into:
translates into:
 
   
 
<haskell>
 
<haskell>
Line 351: Line 453:
 
</haskell>
 
</haskell>
   
  +
where the second argument of <code>(>>=)</code> has the type <span style="white-space: nowrap"><code>a -> IO b</code></span>. It's the way the <code><-</code> binding is processed - the name on the left-hand side of <code><-</code> just becomes a parameter of subsequent operations represented as one large I/O action. Note also that if <code>action1</code> has type <span style="white-space: nowrap"><code>IO a</code></span> then <code>x</code> will just have type <code>a</code>; you can think of the effect of <code><-</code> as "unpacking" the I/O value of <code>action1</code> into <code>x</code>. Note also that <code><-</code> is not a true operator; it's pure syntax, just like <code>do</code> itself. Its meaning results only from the way it gets desugared.
where the second argument of '>>=' has the type "a -> IO b". It's the way
 
the '<-' binding is processed - the name on the left-hand side of '<-' just becomes a parameter of subsequent operations represented as one large IO action. Note also that if 'action1' has type "IO a" then 'x' will just have type "a"; you can think of the effect of '<-' as "unpacking" the IO value of 'action1' into 'x'. Note also that '<-' is not a true operator; it's pure syntax, just like 'do' itself. Its meaning results only from the way it gets desugared.
 
   
Look at the next example:
+
Look at the next example:
   
 
<haskell>
 
<haskell>
Line 374: Line 475:
 
</haskell>
 
</haskell>
   
  +
I omitted the parentheses here; both the <code>(>>)</code> and the <code>(>>=)</code> operators are left-associative, but lambda-bindings always stretches as far to the right as possible, which means that the <code>a</code> and <code>b</code> bindings introduced here are valid for all remaining actions. As an exercise, add the parentheses yourself and translate this definition into the low-level code that explicitly passes "world" values. I think it should be enough to help you finally realize how the <code>do</code> translation and binding operators work.
I omitted the parentheses here; both the '>>' and the '>>=' operators are
 
left-associative, but lambda-bindings always stretches as far to the right as possible, which means that the 'a' and 'b' bindings introduced
 
here are valid for all remaining actions. As an exercise, add the
 
parentheses yourself and translate this procedure into the low-level
 
code that explicitly passes "world" values. I think it should be enough to help you finally realize how the 'do' translation and binding operators work.
 
   
  +
Oh, no! I forgot the third monadic operator: <code>return</code>. After it is simplified, we can see it does very little! It just combines its two parameters - the value passed and the required "world" value - and immediately ''returns'' both of them:
 
Oh, no! I forgot the third monadic operator - 'return'. It just
 
combines its two parameters - the value passed and "world":
 
   
 
<haskell>
 
<haskell>
return :: a -> IO a
 
 
return a world0 = (a, world0)
 
return a world0 = (a, world0)
 
</haskell>
 
</haskell>
   
How about translating a simple example of 'return' usage? Say,
+
How about translating a simple example of <code>return</code> usage? Say,
   
 
<haskell>
 
<haskell>
Line 396: Line 490:
 
</haskell>
 
</haskell>
   
  +
Programmers with an imperative language background often think that <code>return</code> in Haskell, as in other languages, immediately returns from the I/O definition. As you can see in its definition (and even just from its type!), such an assumption is totally wrong. The only purpose of using <code>return</code> is to "lift" some value (of type <code>a</code>) into the result of a whole action (of type <code>IO a</code>) and therefore it should generally be used only as the last executed action of some I/O sequence. For example try to translate the following definition into the corresponding low-level code:
 
Programmers with an imperative language background often think that
 
'return' in Haskell, as in other languages, immediately returns from
 
the IO procedure. As you can see in its definition (and even just from its
 
type!), such an assumption is totally wrong. The only purpose of using
 
'return' is to "lift" some value (of type 'a') into the result of
 
a whole action (of type "IO a") and therefore it should generally be used only as the last executed statement of some IO sequence. For example try to
 
translate the following procedure into the corresponding low-level code:
 
   
 
<haskell>
 
<haskell>
Line 412: Line 499:
 
</haskell>
 
</haskell>
   
and you will realize that the 'print' statement is executed even for non-negative values of 'a'. If you need to escape from the middle of an IO procedure, you can use the 'if' statement:
+
and you will realize that the <code>print</code> call is executed even for non-negative values of <code>a</code>. If you need to escape from the middle of an I/O definition, you can use an <code>if</code> expression:
   
 
<haskell>
 
<haskell>
Line 431: Line 518:
 
</haskell>
 
</haskell>
   
that may be useful for escaping from the middle of a longish 'do' statement.
+
that may be useful for escaping from the middle of a longish <code>do</code>-expression.
   
  +
Last exercise: implement a function <code>liftM</code> that lifts operations on plain values to the operations on monadic ones. Its type signature:
 
Last exercise: implement a function 'liftM' that lifts operations on
 
plain values to the operations on monadic ones. Its type signature:
 
   
 
<haskell>
 
<haskell>
Line 441: Line 526:
 
</haskell>
 
</haskell>
   
If that's too hard for you, start with the following high-level
+
If that's too hard for you, start with the following high-level definition and rewrite it in low-level fashion:
definition and rewrite it in low-level fashion:
 
   
 
<haskell>
 
<haskell>
Line 448: Line 532:
 
return (f x)
 
return (f x)
 
</haskell>
 
</haskell>
 
   
   
 
== Mutable data (references, arrays, hash tables...) ==
 
== Mutable data (references, arrays, hash tables...) ==
   
As you should know, every name in Haskell is bound to one fixed (immutable) value. This greatly simplifies understanding algorithms and code optimization, but it's inappropriate in some cases. As we all know, there are plenty of algorithms that are simpler to implement in terms of updatable
+
As you should know, every name in Haskell is bound to one fixed (immutable) value. This greatly simplifies understanding algorithms and code optimization, but it's inappropriate in some cases. As we all know, there are plenty of algorithms that are simpler to implement in terms of updatable variables, arrays and so on. This means that the value associated with a variable, for example, can be different at different execution points, so reading its value can't be considered as a pure function. Imagine, for example, the following code:
variables, arrays and so on. This means that the value associated with
 
a variable, for example, can be different at different execution points,
 
so reading its value can't be considered as a pure function. Imagine,
 
for example, the following code:
 
   
 
<haskell>
 
<haskell>
Line 466: Line 545:
 
</haskell>
 
</haskell>
   
  +
Does this look strange?
Does this look strange? First, the two calls to 'readVariable' look the same, so the compiler can just reuse the value returned by the first call. Second,
 
  +
# The two calls to <code>readVariable</code> look the same, so the compiler can just reuse the value returned by the first call.
the result of the 'writeVariable' call isn't used so the compiler can (and will!) omit this call completely. To complete the picture, these three calls may be rearranged in any order because they appear to be independent of each
 
  +
# The result of the <code>writeVariable</code> call isn't used so the compiler can (and will!) omit this call completely.
other. This is obviously not what was intended. What's the solution? You already know this - use IO actions! Using IO actions guarantees that:
 
  +
# These three calls may be rearranged in any order because they appear to be independent of each other.
   
  +
This is obviously not what was intended. What's the solution? You already know this - use I/O actions! Doing that guarantees:
# the execution order will be retained as written
 
  +
  +
# the result of the "same" action (such as <span style="white-space: nowrap"><code>readVariable varA</code></span>) will not be reused
 
# each action will have to be executed
 
# each action will have to be executed
  +
# the execution order will be retained as written
# the result of the "same" action (such as "readVariable varA") will not be reused
 
   
 
So, the code above really should be written as:
 
So, the code above really should be written as:
   
 
<haskell>
 
<haskell>
  +
import Data.IORef
 
main = do varA <- newIORef 0 -- Create and initialize a new variable
 
main = do varA <- newIORef 0 -- Create and initialize a new variable
 
a0 <- readIORef varA
 
a0 <- readIORef varA
Line 484: Line 567:
 
</haskell>
 
</haskell>
   
  +
Here, <code>varA</code> has the type <span style="white-space: nowrap"><code>IORef Int</code></span> which means "a variable (reference) in the I/O monad holding a value of type <code>Int</code>". <code>newIORef</code> creates a new variable (reference) and returns it, and then read/write actions use this reference. The value returned by the <span style="white-space: nowrap"><code>readIORef varA</code></span> action depends not only on the variable involved but also on the moment this operation is performed so it can return different values on each call.
Here, 'varA' has the type "IORef Int" which means "a variable (reference) in
 
the IO monad holding a value of type Int". newIORef creates a new variable
 
(reference) and returns it, and then read/write actions use this
 
reference. The value returned by the "readIORef varA" action depends not
 
only on the variable involved but also on the moment this operation is performed so it can return different values on each call.
 
   
  +
Arrays, hash tables and any other _mutable_ data structures are defined in the same way - for each of them, there's an operation that creates new "mutable values" and returns a reference to it. Then value-specific read and write operations in the I/O monad are used. The following code shows an example using mutable arrays:
Arrays, hash tables and any other _mutable_ data structures are
 
defined in the same way - for each of them, there's an operation that creates new "mutable values" and returns a reference to it. Then special read and write
 
operations in the IO monad are used. The following code shows an example
 
using mutable arrays:
 
   
 
<haskell>
 
<haskell>
import Data.Array.IO
+
import Data.Array.IO
main = do arr <- newArray (1,10) 37 :: IO (IOArray Int Int)
+
main = do arr <- newArray (1,10) 37 :: IO (IOArray Int Int)
a <- readArray arr 1
+
a <- readArray arr 1
writeArray arr 1 64
+
writeArray arr 1 64
b <- readArray arr 1
+
b <- readArray arr 1
print (a, b)
+
print (a, b)
 
</haskell>
 
</haskell>
   
Here, an array of 10 elements with 37 as the initial value at each location is created. After reading the value of the first element (index 1) into 'a' this element's value is changed to 64 and then read again into 'b'. As you can see by executing this code, 'a' will be set to 37 and 'b' to 64.
+
Here, an array of 10 elements with 37 as the initial value at each location is created. After reading the value of the first element (index 1) into <code>a</code> this element's value is changed to 64 and then read again into <code>b</code>. As you can see by executing this code, <code>a</code> will be set to 37 and <code>b</code> to 64.
 
   
  +
Other state-dependent operations are also often implemented with I/O actions. For example, a random number generator should return a different value on each call. It looks natural to give it a type involving <code>IO</code>:
 
Other state-dependent operations are also often implemented as IO
 
actions. For example, a random number generator should return a different
 
value on each call. It looks natural to give it a type involving IO:
 
   
 
<haskell>
 
<haskell>
Line 516: Line 588:
 
</haskell>
 
</haskell>
   
  +
Moreover, when you import a C routine you should be careful - if this routine is impure, i.e. its result depends on something "outside the Haskell program" (file system, memory contents, its own <code>static</code> internal state and so on), you should give it an <code>IO</code> type. Otherwise, the compiler can "optimize" repetitive calls to the definition with the same parameters!
Moreover, when you import C routines you should be careful - if this
 
routine is impure, i.e. its result depends on something in the "real
 
world" (file system, memory contents...), internal state and so on,
 
you should give it an IO type. Otherwise, the compiler can
 
"optimize" repetitive calls of this procedure with the same parameters! :)
 
   
For example, we can write a non-IO type for:
+
For example, we can write a non-<code>IO</code> type for:
   
 
<haskell>
 
<haskell>
Line 529: Line 597:
 
</haskell>
 
</haskell>
   
because the result of 'sin' depends only on its argument, but
+
because the result of <code>sin</code> depends only on its argument, but
   
 
<haskell>
 
<haskell>
Line 536: Line 604:
 
</haskell>
 
</haskell>
   
If you will declare 'tell' as a pure function (without IO) then you may
+
If you will declare <code>tell</code> as a pure function (without <code>IO</code>) then you may get the same position on each call!
get the same position on each call! :)
 
   
== IO actions as values ==
+
=== Encapsulated mutable data: ST ===
   
  +
If you're going to be doing things like sending text to a screen or reading data from a scanner, <code>IO</code> is the type to start with - you can then customise existing I/O operations or add new ones as you see fit. But what if that shiny-new (or classic) algorithm you're working on really only needs mutable state - then having to drag that <code>IO</code> type from <code>main</code> all the way through to wherever you're implementing the algorithm can get quite irritating.
By this point you should understand why it's impossible to use IO
 
actions inside non-IO (pure) procedures. Such procedures just don't
 
get a "baton"; they don't know any "world" value to pass to an IO action.
 
The RealWorld type is an abstract datatype, so pure functions also can't construct RealWorld values by themselves, and it's a strict type, so 'undefined' also can't be used. So, the prohibition of using IO actions inside pure procedures is just a type system trick (as it usually is in Haskell :)).
 
   
  +
Fortunately there is a better way! One that remains totally pure and yet allows the use of references, arrays, and so on - and it's done using, you guessed it, Haskell's versatile type system (and one extension).
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, returned as results, collected in
 
lists, and partially applied. But an IO action will remain a
 
functional value because we can't apply it to the last argument - of
 
type RealWorld.
 
   
  +
Remember our definition of <code>IO</code>?
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 its "actions chain". And real execution of this action will take
 
place only when this procedure is called as part of the process of
 
"calculating the final value of world" for 'main'. Look at this example:
 
   
 
<haskell>
 
<haskell>
  +
newtype IO a = Act (RealWorld -> (a, RealWorld))
main world0 = let get2chars = getChar >> getChar
 
  +
</haskell>
  +
  +
Well, the new <code>ST</code> type makes just one change:
  +
  +
<haskell>
  +
newtype ST s a = Act' (s -> (a, s))
  +
</haskell>
  +
  +
If we wanted to, we could use <code>ST</code> to define <code>IO</code>:
  +
  +
<haskell>
  +
type IO a = ST RealWorld a
  +
</haskell>
  +
  +
Let's add some extra definitions:
  +
  +
<haskell>
  +
newSTRef :: a -> ST s (STRef s a) -- these are
  +
readSTRef :: STRef s a -> ST s a -- usually
  +
writeSTRef :: STRef s a -> a -> ST s () -- primitive
  +
  +
newSTArray :: Ix i => (i, i) -> ST s (STArray s i e) -- also usually primitive
  +
  +
  +
instance Monad (ST s) where
  +
m >>= k = let actual' (Act' m) = m in
  +
Act' $ \s1 -> case actual' m s1 of (x, s2) -> actual' (k x) s2
  +
return x = Act' $ \s1 -> (x, s1)
  +
</haskell>
  +
  +
...that's right - this new <code>ST</code> type is also monadic!
  +
  +
So what's the big difference between the <code>ST</code> and <code>IO</code> types? In one word - <code>runST</code>:
  +
<haskell>
  +
runST :: (forall s . ST s a) -> a
  +
</haskell>
  +
  +
Yes - it has a very unusual type. But that type allows you to run your stateful computation ''as if it was a pure definition!''
  +
  +
The <code>s</code> type variable in <code>ST</code> is the type of the local state. Moreover, all the fun mutable stuff available for <code>ST</code> is quantified over <code>s</code>:
  +
<haskell>
  +
newSTRef :: a -> ST s (STRef s a)
  +
newArray_ :: Ix i => (i, i) -> ST s (STArray s i e)
  +
</haskell>
  +
  +
So why does <code>runST</code> have such a funky type? Let's see what would happen if we wrote
  +
<haskell>
  +
makeSTRef :: a -> STRef s a
  +
makeSTRef a = runST (newSTRef a)
  +
</haskell>
  +
This fails, because <code>newSTRef a</code> doesn't work for all state types <code>s</code> - it only works for the <code>s</code> from the return type <span style="white-space: nowrap"><code>STRef s a</code></span>.
  +
  +
This is all sort of wacky, but the result is that you can only run an <code>ST</code> computation where the output type is functionally pure, and makes no references to the internal mutable state of the computation. In exchange for that, there's no access to I/O operations like writing to or reading from the console. The monadic <code>ST</code> type only has references, arrays, and such that are useful for performing pure computations.
  +
  +
Just like <code>RealWorld</code>, the state type doesn't actually mean anything. We never have an actual value of type <code>s</code>, for instance. It's just a way of getting the type system to do the work of ensuring purity is preserved - it's being used like another baton.
  +
  +
On the inside <code>runST</code> uses that newly-made baton to run the computation. When it finishes <code>runST</code> separates the resulting value from the final baton. This value is then returned by <code>runST</code>.
  +
  +
Because the internal implementations of <code>IO</code> and <code>ST</code> are so similar, there's this function:
  +
  +
<haskell>
  +
stToIO :: ST RealWorld a -> IO a
  +
</haskell>
  +
  +
The difference is that <code>ST</code> uses the type system to forbid unsafe behavior like extracting mutable objects from their safe <code>ST</code> wrapping, but allowing purely functional outputs to be performed with all the handy access to mutable references and arrays.
  +
  +
For example, here's a particularly convoluted way to compute the integer that comes after zero:
  +
  +
<haskell>
  +
oneST :: ST s Integer -- note that this works correctly for any s
  +
oneST = do var <- newSTRef 0
  +
modifySTRef var (+1)
  +
readSTRef var
  +
  +
one :: Int
  +
one = runST oneST
  +
</haskell>
  +
  +
  +
== I/O actions as values ==
  +
  +
By this point you should understand why it's impossible to use I/O actions inside non-I/O (pure) functions. Such functions just don't get a "baton"; they don't know any "world" value to pass to an I/O action. The <code>RealWorld</code> type is an abstract datatype, so pure functions also can't construct <code>RealWorld</code> values by themselves, and it's a strict type, so <code>undefined</code> also can't be used. So, the prohibition of using I/O actions inside pure functions is maintained by the type system (as it usually is in Haskell).
  +
  +
But while pure code can't ''execute'' I/O actions, it can work with them as with any other functional values - they can be stored in data structures, passed as parameters, returned as results, collected in lists, and partially applied. But an I/O action will remain a functional value because we can't apply it to the last argument - of type <code>RealWorld</code>.
  +
  +
In order to ''execute'' the I/O action we need to apply it to some <code>RealWorld</code> value. That can be done only inside other I/O actions, in their "actions chains". And real execution of this action will take place only when this action is called as part of the process of "calculating the final value of world" for <code>main</code>. Look at this partially-simplified example:
  +
  +
<haskell>
  +
main world0 = let skip2chars = getChar >> getChar >> return () -- NB: not simplified!
  +
(answer, world2) = skip2chars world1
 
((), world1) = putStr "Press two keys" world0
 
((), world1) = putStr "Press two keys" world0
(answer, world2) = get2chars world1
 
 
in ((), world2)
 
in ((), world2)
 
</haskell>
 
</haskell>
  +
 
  +
Here we first write a binding for <code>skip2chars</code>, then another binding involving <code>putStr</code>. But what's the execution order? It's not defined by the order of the <code>let</code> bindings, it's defined by the order of processing "world" values! You can arbitrarily reorder those local bindings - the execution order will be defined by the data dependency with respect to the "world" values that get passed around. Let's see what this <code>main</code> action would have looked like in the <code>do</code> notation:
Here we first bind a value to 'get2chars' and then write a binding
 
involving 'putStr'. But what's the execution order? It's not defined
 
by the order of the 'let' bindings, it's defined by the order of processing
 
"world" values! You can arbitrarily reorder the binding statements - the execution order will be defined by the data dependency with respect to the
 
"world" values that get passed around. Let's see what this 'main' looks like in the 'do' notation:
 
   
 
<haskell>
 
<haskell>
main = do let get2chars = getChar >> getChar
+
main = do let skip2chars = getChar >> getChar >> return ()
 
putStr "Press two keys"
 
putStr "Press two keys"
get2chars
+
skip2chars
 
return ()
 
return ()
 
</haskell>
 
</haskell>
   
As you can see, we've eliminated two of the 'let' bindings and left only the one defining 'get2chars'. The non-'let' statements are executed in the exact order in which they're written, because they pass the "world" value from statement to statement as we described above. Thus, this version of the function is much easier to understand because we don't have to mentally figure out the data dependency of the "world" value.
+
As you can see, we've eliminated two of the <code>let</code> bindings and left only the one defining <code>skip2chars</code>. The non-<code>let</code> actions are executed in the exact order in which they're written, because they pass the "world" value from action to action as we described above. Thus, this version of the function is much easier to understand because we don't have to mentally figure out the data dependency of the "world" value.
   
  +
Moreover, I/O actions like <code>skip2chars</code> can't be executed directly because they are functions with a <code>RealWorld</code> parameter. To execute them, we need to supply the <code>RealWorld</code> parameter, i.e. insert them in the <code>main</code> chain, placing them in some <code>do</code> sequence executed from <code>main</code> (either directly in the <code>main</code> action, or indirectly in an I/O function called from <code>main</code>). Until that's done, they will remain like any function, in partially evaluated form. And we can work with I/O actions as with any other functions - bind them to names (as we did above), save them in data structures, pass them as function parameters and return them as results - and they won't be performed until you give them that inaugural <code>RealWorld</code> argument!
Moreover, IO actions like 'get2chars' can't be executed directly
 
because they are functions with a RealWorld parameter. To execute them,
 
we need to supply the RealWorld parameter, i.e. insert them in the 'main'
 
chain, placing them in some 'do' sequence executed from 'main' (either directly in the 'main' function, or indirectly in an IO function called from 'main'). Until that's done, they will remain like any function, in partially
 
evaluated form. And we can work with IO actions as with any other
 
functions - bind them to names (as we did above), save them in data
 
structures, pass them as function parameters and return them as results - and
 
they won't be performed until you give them the magic RealWorld
 
parameter!
 
   
  +
=== Example: a list of I/O actions ===
   
  +
Let's try defining a list of I/O actions:
 
=== Example: a list of IO actions ===
 
 
Let's try defining a list of IO actions:
 
   
 
<haskell>
 
<haskell>
Line 605: Line 735:
 
</haskell>
 
</haskell>
   
I used additional parentheses around each action, although they aren't really required. If you still can't believe that these actions won't be executed immediately, just recall the real type of this list:
+
I used additional parentheses around each action, although they aren't really required. If you still can't believe that these actions won't be executed immediately, just recall the simplifed type of this list:
  +
 
 
<haskell>
 
<haskell>
 
ioActions :: [RealWorld -> ((), RealWorld)]
 
ioActions :: [RealWorld -> ((), RealWorld)]
 
</haskell>
 
</haskell>
   
Well, now we want to execute some of these actions. No problem, just
+
Well, now we want to execute some of these actions. No problem, just insert them into the <code>main</code> chain:
insert them into the 'main' chain:
 
   
 
<haskell>
 
<haskell>
Line 620: Line 749:
 
</haskell>
 
</haskell>
   
  +
Looks strange, right? Really, any I/O action that you write in a <code>do</code>-expression (or use as a parameter for the <code>(>>)</code>/<code>(>>=)</code> operators) is an expression returning a result of type <span style="white-space: nowrap"><code>IO a</code></span> for some type <code>a</code>. Typically, you use some function that has the type <span style="white-space: nowrap"><code>x -> y -> ... -> IO a</code></span> and provide all the <code>x</code>, <code>y</code>, etc. parameters. But you're not limited to this standard scenario - don't forget that Haskell is a functional language and you're free to compute the functional value required (recall that <span style="white-space: nowrap"><code>IO a</code></span> is really 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 the previous example - that's also OK. Want to see this functional value passed as a parameter? Just look at the definition of <code>when</code>. Hey, we can buy, sell, and rent these I/O actions just like we can with any other functional values! For example, let's define a function that executes all the I/O actions in the list:
Looks strange, right? :) Really, any IO action that you write in a 'do'
 
statement (or use as a parameter for the '>>'/'>>=' operators) is an expression
 
returning a result of type 'IO a' for some type 'a'. Typically, you use some function that has the type 'x -> y -> ... -> IO a' and provide all the x, y, etc. parameters. But you're not limited to this standard scenario -
 
don't forget that Haskell is a functional language and you're free to
 
compute the functional value required (recall that "IO a" is really 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 the previous example - that's also
 
OK. Want to see this functional value passed as a parameter?
 
Just look at the definition of 'when'. Hey, we can buy, sell, and rent
 
these IO actions just like we can with any other functional values! For example, let's define a function that executes all the IO actions in the list:
 
   
 
<haskell>
 
<haskell>
Line 639: Line 758:
 
</haskell>
 
</haskell>
   
  +
No mirrors or smoke - we just extract I/O actions from the list and insert them into a chain of I/O operations that should be performed one after another (in the same order that they occurred in the list) to "compute the final world value" of the entire <code>sequence_</code> call.
No black magic - we just extract IO actions from the list and insert
 
them into a chain of IO operations that should be performed one after another (in the same order that they occurred in the list) to "compute the final world value" of the entire 'sequence_' call.
 
   
With the help of 'sequence_', we can rewrite our last 'main' function as:
+
With the help of <code>sequence_</code>, we can rewrite our last <code>main</code> action as:
   
 
<haskell>
 
<haskell>
Line 648: Line 766:
 
</haskell>
 
</haskell>
   
  +
Haskell's ability to work with I/O actions as with any other (functional and non-functional) values allows us to define control structures of arbitrary complexity. Try, for example, to define a control structure that repeats an action until it returns the <code>False</code> result:
 
Haskell's ability to work with IO actions as with any other
 
(functional and non-functional) values allows us to define control
 
structures of arbitrary complexity. Try, for example, to define a control
 
structure that repeats an action until it returns the 'False' result:
 
   
 
<haskell>
 
<haskell>
Line 661: Line 775:
 
Most programming languages don't allow you to define control structures at all, and those that do often require you to use a macro-expansion system. In Haskell, control structures are just trivial functions anyone can write.
 
Most programming languages don't allow you to define control structures at all, and those that do often require you to use a macro-expansion system. In Haskell, control structures are just trivial functions anyone can write.
   
  +
=== Example: returning an I/O action as a result ===
   
  +
How about returning an I/O action as the result of a function? Well, we've done this for each I/O definition - they all return I/O actions that need a <code>RealWorld</code> value to be performed. While we usually just execute them as part of a higher-level I/O definition, it's also possible to just collect them without actual execution:
=== Example: returning an IO action as a result ===
 
 
How about returning an IO action as the result of a function? Well, we've done
 
this each time we've defined an IO procedure - they all return IO actions
 
that need a RealWorld value to be performed. While we usually just
 
execute them as part of a higher-level IO procedure, it's also
 
possible to just collect them without actual execution:
 
   
 
<haskell>
 
<haskell>
 
main = do let a = sequence ioActions
 
main = do let a = sequence ioActions
 
b = when True getChar
 
b = when True getChar
c = getChar >> getChar
+
c = getChar >> getChar >> return ()
putStr "These 'let' statements are not executed!"
+
putStr "These let-bindings are not executed!"
 
</haskell>
 
</haskell>
   
These assigned IO procedures can be used as parameters to other
+
These assigned I/O actions can be used as parameters to other definitions, or written to global variables, or processed in some other way, or just executed later, as we did in the example with <code>skip2chars</code>.
procedures, or written to global variables, or processed in some other
 
way, or just executed later, as we did in the example with 'get2chars'.
 
   
But how about returning a parameterized IO action from an IO procedure? Let's define a procedure that returns the i'th byte from a file represented as a Handle:
+
But how about returning a parameterized I/O action from an I/O definition? Here's a definition that returns the i'th byte from a file represented as a Handle:
   
 
<haskell>
 
<haskell>
readi h i = do hSeek h i AbsoluteSeek
+
readi h i = do hSeek h AbsoluteSeek i
 
hGetChar h
 
hGetChar h
 
</haskell>
 
</haskell>
   
So far so good. But how about a procedure that returns the i'th byte of a file
+
So far so good. But how about a definition that returns the i'th byte of a file with a given name without reopening it each time?
with a given name without reopening it each time?
 
   
 
<haskell>
 
<haskell>
Line 697: Line 803:
 
</haskell>
 
</haskell>
   
As you can see, it's an IO procedure that opens a file and returns...
+
As you can see, it's an I/O definition that opens a file and returns...an I/O action that will read the specified byte. But we can go further and include the <code>readi</code> body in <code>readfilei</code>:
another IO procedure that will read the specified byte. But we can go
 
further and include the 'readi' body in 'readfilei':
 
   
 
<haskell>
 
<haskell>
 
readfilei name = do h <- openFile name ReadMode
 
readfilei name = do h <- openFile name ReadMode
let readi h i = do hSeek h i AbsoluteSeek
+
let readi h i = do hSeek h AbsoluteSeek i
 
hGetChar h
 
hGetChar h
 
return (readi h)
 
return (readi h)
 
</haskell>
 
</haskell>
   
That's a little better. But why do we add 'h' as a parameter to 'readi' if it can be obtained from the environment where 'readi' is now defined? An even shorter version is this:
+
That's a little better. But why do we add <code>h</code> as a parameter to <code>readi</code> if it can be obtained from the environment where <code>readi</code> is now defined? An even shorter version is this:
   
 
<haskell>
 
<haskell>
 
readfilei name = do h <- openFile name ReadMode
 
readfilei name = do h <- openFile name ReadMode
let readi i = do hSeek h i AbsoluteSeek
+
let readi i = do hSeek h AbsoluteSeek i
 
hGetChar h
 
hGetChar h
 
return readi
 
return readi
 
</haskell>
 
</haskell>
   
What have we done here? We've build a parameterized IO action involving local
+
What have we done here? We've build a parameterized I/O action involving local names inside <code>readfilei</code> and returned it as the result. Now it can be used in the following way:
names inside 'readfilei' and returned it as the result. Now it can be
 
used in the following way:
 
   
 
<haskell>
 
<haskell>
Line 728: Line 830:
 
</haskell>
 
</haskell>
   
  +
This way of using I/O actions is very typical for Haskell programs - you just construct one or more I/O actions that you need, with or without parameters, possibly involving the parameters that your "constructor" received, and return them to the caller. Then these I/O actions can be used in the rest of the program without any knowledge about your internal implementation strategy. One thing this can be used for is to partially emulate the OOP (or more precisely, the ADT) programming paradigm.
 
This way of using IO actions is very typical for Haskell programs - you
 
just construct one or more IO actions that you need,
 
with or without parameters, possibly involving the parameters that your
 
"constructor" received, and return them to the caller. Then these IO actions
 
can be used in the rest of the program without any knowledge about your
 
internal implementation strategy. One thing this can be used for is to
 
partially emulate the OOP (or more precisely, the ADT) programming paradigm.
 
 
   
 
=== Example: a memory allocator generator ===
 
=== Example: a memory allocator generator ===
   
As an example, one of my programs has a module which is a memory suballocator. It receives the address and size of a large memory block and returns two
+
As an example, one of my programs has a module which is a memory suballocator. It receives the address and size of a large memory block and returns two specialised I/O operations - one to allocate a subblock of a given size and the other to free the allocated subblock:
procedures - one to allocate a subblock of a given size and the other to
 
free the allocated subblock:
 
   
 
<haskell>
 
<haskell>
Line 756: Line 848:
 
</haskell>
 
</haskell>
   
  +
How this is implemented? <code>alloc</code> and <code>free</code> work with references created inside the <code>memoryAllocator</code> definition. Because the creation of these references is a part of the <code>memoryAllocator</code> I/O-action chain, a new independent set of references will be created for each memory block for which <code>memoryAllocator</code> is called:
How this is implemented? 'alloc' and 'free' work with references
 
created inside the memoryAllocator procedure. Because the creation of these references is a part of the memoryAllocator IO actions chain, a new independent set of references will be created for each memory block for which
 
memoryAllocator is called:
 
   
 
<haskell>
 
<haskell>
memoryAllocator buf size = do start <- newIORef buf
+
memoryAllocator buf size =
end <- newIORef (buf `plusPtr` size)
+
do start <- newIORef buf
  +
end <- newIORef (buf `plusPtr` size)
...
 
  +
...
 
</haskell>
 
</haskell>
   
These two references are read and written in the 'alloc' and 'free' definitions (we'll implement a very simple memory allocator for this example):
+
These two references are read and written in the <code>alloc</code> and <code>free</code> definitions (we'll implement a very simple memory allocator for this example):
   
 
<haskell>
 
<haskell>
Line 773: Line 864:
 
writeIORef start (addr `plusPtr` size)
 
writeIORef start (addr `plusPtr` size)
 
return addr
 
return addr
  +
 
 
let free ptr = do writeIORef start ptr
 
let free ptr = do writeIORef start ptr
 
</haskell>
 
</haskell>
   
What we've defined here is just a pair of closures that use state
+
What we've defined here is just a pair of closures that use state available at the moment of their definition. As you can see, it's as easy as in any other functional language, despite Haskell's lack of direct support for impure routines.
  +
available at the moment of their definition. As you can see, it's as
 
  +
The following example uses the operations returned by <code>memoryAllocator</code>, to simultaneously allocate/free blocks in two independent memory buffers:
easy as in any other functional language, despite Haskell's lack
 
of direct support for impure functions.
 
 
The following example uses procedures, returned by memoryAllocator, to
 
simultaneously allocate/free blocks in two independent memory buffers:
 
   
 
<haskell>
 
<haskell>
Line 797: Line 884:
 
ptr22 <- alloc2 1000
 
ptr22 <- alloc2 1000
 
</haskell>
 
</haskell>
 
 
   
 
=== Example: emulating OOP with record types ===
 
=== Example: emulating OOP with record types ===
   
  +
Let's implement the classical OOP example: drawing figures. There are figures of different types: circles, rectangles and so on. The task is to create a heterogeneous list of figures. All figures in this list should support the same set of operations: draw, move and so on. We will define these operations using I/O actions. Instead of a "class" let's define a structure containing implementations of all the operations required:
Let's implement the classical OOP example: drawing figures. There are
 
figures of different types: circles, rectangles and so on. The task is
 
to create a heterogeneous list of figures. All figures in this list should
 
support the same set of operations: draw, move and so on. We will
 
represent these operations as IO procedures. Instead of a "class" let's
 
define a structure containing implementations of all the procedures
 
required:
 
   
 
<haskell>
 
<haskell>
Line 818: Line 897:
 
</haskell>
 
</haskell>
   
  +
The constructor of each figure's type should just return a <code>Figure</code> record:
 
The constructor of each figure's type should just return a Figure record:
 
   
 
<haskell>
 
<haskell>
Line 829: Line 907:
 
</haskell>
 
</haskell>
   
  +
We will "draw" figures by just printing their current parameters. Let's start with a simplified implementation of the <code>circle</code> and <code>rectangle</code> constructors, without actual <code>move</code> support:
 
We will "draw" figures by just printing their current parameters.
 
Let's start with a simplified implementation of the 'circle' and 'rectangle'
 
constructors, without actual 'move' support:
 
   
 
<haskell>
 
<haskell>
Line 844: Line 919:
 
</haskell>
 
</haskell>
   
  +
As you see, each constructor just returns a fixed <code>draw</code> operation that prints parameters with which the concrete figure was created. Let's test it:
 
As you see, each constructor just returns a fixed 'draw' procedure that prints
 
parameters with which the concrete figure was created. Let's test it:
 
   
 
<haskell>
 
<haskell>
Line 860: Line 933:
 
</haskell>
 
</haskell>
   
  +
Now let's define "full-featured" figures that can actually be moved around. In order to achieve this, we should provide each figure with a mutable variable that holds each figure's current screen location. The type of this variable will be <span style="white-space: nowrap"><code>IORef Point</code></span>. This variable should be created in the figure constructor and manipulated in I/O operations (closures) enclosed in the <code>Figure</code> record:
 
Now let's define "full-featured" figures that can actually be
 
moved around. In order to achieve this, we should provide each figure
 
with a mutable variable that holds each figure's current screen location. The
 
type of this variable will be "IORef Point". This variable should be created in the figure constructor and manipulated in IO procedures (closures) enclosed in
 
the Figure record:
 
   
 
<haskell>
 
<haskell>
 
circle center radius = do
 
circle center radius = do
 
centerVar <- newIORef center
 
centerVar <- newIORef center
  +
 
 
let drawF = do center <- readIORef centerVar
 
let drawF = do center <- readIORef centerVar
 
putStrLn (" Circle at "++show center
 
putStrLn (" Circle at "++show center
 
++" with radius "++show radius)
 
++" with radius "++show radius)
  +
 
 
let moveF (addX,addY) = do (x,y) <- readIORef centerVar
 
let moveF (addX,addY) = do (x,y) <- readIORef centerVar
 
writeIORef centerVar (x+addX, y+addY)
 
writeIORef centerVar (x+addX, y+addY)
  +
 
 
return $ Figure { draw=drawF, move=moveF }
 
return $ Figure { draw=drawF, move=moveF }
   
 
 
rectangle from to = do
 
rectangle from to = do
 
fromVar <- newIORef from
 
fromVar <- newIORef from
Line 888: Line 955:
 
to <- readIORef toVar
 
to <- readIORef toVar
 
putStrLn (" Rectangle "++show from++"-"++show to)
 
putStrLn (" Rectangle "++show from++"-"++show to)
  +
 
 
let moveF (addX,addY) = do (fromX,fromY) <- readIORef fromVar
 
let moveF (addX,addY) = do (fromX,fromY) <- readIORef fromVar
 
(toX,toY) <- readIORef toVar
 
(toX,toY) <- readIORef toVar
Line 896: Line 963:
 
return $ Figure { draw=drawF, move=moveF }
 
return $ Figure { draw=drawF, move=moveF }
 
</haskell>
 
</haskell>
 
   
 
Now we can test the code which moves figures around:
 
Now we can test the code which moves figures around:
Line 908: Line 974:
 
</haskell>
 
</haskell>
   
  +
It's important to realize that we are not limited to including only I/O actions in a record that's intended to simulate a C++/Java-style interface. The record can also include values, <code>IORef</code>s, pure functions - in short, any type of data. For example, we can easily add to the <code>Figure</code> interface fields for area and origin:
 
It's important to realize that we are not limited to including only IO actions
 
in a record that's intended to simulate a C++/Java-style interface. The record can also include values, IORefs, pure functions - in short, any type of data. For example, we can easily add to the Figure interface fields for area and origin:
 
   
 
<haskell>
 
<haskell>
Line 921: Line 985:
   
   
  +
== Exception handling (under development) ==
   
  +
Although Haskell provides a set of exception raising/handling features comparable to those in popular OOP languages (C++, Java, C#), this part of the language receives much less attention. This is for two reasons:
== Dark side of IO monad ==
 
=== unsafePerformIO ===
 
   
  +
* you just don't need to worry as much about them - most of the time it just works "behind the scenes".
Programmers coming from an imperative language background often look for a way to execute IO actions inside a pure procedure. But what does this mean?
 
  +
Imagine that you're trying to write a procedure that reads the contents of a file with a given name, and you try to write it as a pure (non-IO) function:
 
  +
* Haskell, lacking OOP-style inheritance, doesn't allow the programmer to easily subclass exception types, therefore limiting the flexibility of exception handling.
  +
  +
The Haskell RTS raises more exceptions than traditional languages - pattern match failures, calls with invalid arguments (such as <span style="white-space: nowrap"><code>head []</code></span>) and computations whose results depend on special values <code>undefined</code> and <span style="white-space: nowrap"><code>error "...."</code></span> all raise their own exceptions:
  +
  +
* example 1:
  +
:<haskell>
  +
main = print (f 2)
  +
  +
f 0 = "zero"
  +
f 1 = "one"
  +
</haskell>
  +
  +
* example 2:
  +
:<haskell>
  +
main = print (head [])
  +
</haskell>
  +
  +
* example 3:
  +
:<haskell>
  +
main = print (1 + (error "Value that wasn't initialized or cannot be computed"))
  +
</haskell>
  +
  +
This allows the writing of programs in a much more error-prone way.
  +
  +
  +
== Interfacing with C/C++ and foreign libraries (under development) ==
  +
  +
While Haskell is great at algorithm development, speed isn't its best side. We can combine the best of both languages, though, by writing speed-critical parts of program in C and the rest in Haskell. We just need a way to call C routines from Haskell and vice versa, and to marshal data between the two languages.
  +
  +
We also need to interact with C to use Windows/Linux APIs, linking to various libraries and DLLs. Even interfacing with other languages often requires going through C, which acts as a "common denominator". [https://www.haskell.org/onlinereport/haskell2010/haskellch8.html Chapter 8 of the Haskell 2010 report] provides a complete description of interfacing with C.
  +
  +
We will learn to use the FFI via a series of examples. These examples include C/C++ code, so they need C/C++ compilers to be installed, the same will be true if you need to include code written in C/C++ in your program (C/C++ compilers are not required when you just need to link with existing libraries providing APIs with C calling convention). On Unix (and Mac OS?) systems, the system-wide default C/C++ compiler is typically used by GHC installation. On Windows, no default compilers exist, so GHC is typically shipped with a C compiler, and you may find on the download page a GHC distribution bundled with C and C++ compilers. Alternatively, you may find and install a GCC/MinGW version compatible with your GHC installation.
  +
  +
If you need to make your C/C++ code as fast as possible, you may compile your code by Intel compilers instead of GCC. However, these compilers are not free, moreover on Windows, code compiled by Intel compilers may not interact correctly with GHC-compiled code, unless one of them is put into DLLs (due to object file incompatibility).
  +
  +
[http://www.haskell.org/haskellwiki/Applications_and_libraries/Interfacing_other_languages More links]:
  +
  +
;[http://www.cse.unsw.edu.au/~chak/haskell/c2hs/ C-&gt;Haskell]
  +
:A lightweight tool for implementing access to C libraries from Haskell.
  +
  +
;[[HSFFIG]]
  +
:The Haskell FFI Binding Modules Generator (HSFFIG) is a tool that takes a C library header (".h") and generates Haskell Foreign Function Interface import declarations for items (functions, structures, etc.) the header defines.
  +
  +
;[http://quux.org/devel/missingpy MissingPy]
  +
:MissingPy is really two libraries in one. At its lowest level, MissingPy is a library designed to make it easy to call into Python from Haskell. It provides full support for interpreting arbitrary Python code, interfacing with a good part of the Python/C API, and handling Python objects. It also provides tools for converting between Python objects and their Haskell equivalents. Memory management is handled for you, and Python exceptions get mapped to Haskell <code>Dynamic</code> exceptions. At a higher level, MissingPy contains Haskell interfaces to some Python modules.
  +
  +
;[[HsLua]]
  +
:A Haskell interface to the Lua scripting language
  +
  +
=== Foreign calls ===
  +
  +
We begin by learning how to call C routines from Haskell and Haskell definitions from C. The first example consists of three files:
  +
  +
''main.hs:''
  +
<haskell>
  +
{-# LANGUAGE ForeignFunctionInterface #-}
  +
  +
main = do print "Hello from main"
  +
c_routine
  +
  +
haskell_definition = print "Hello from haskell_definition"
  +
  +
foreign import ccall safe "prototypes.h"
  +
c_routine :: IO ()
  +
  +
foreign export ccall
  +
haskell_definition :: IO ()
  +
</haskell>
  +
  +
''vile.c:''
  +
<haskell>
  +
#include <stdio.h>
  +
#include "prototypes.h"
  +
  +
void c_routine (void)
  +
{
  +
printf("Hello from c_routine\n");
  +
haskell_definition();
  +
}
  +
</haskell>
  +
  +
''prototypes.h:''
  +
<haskell>
  +
extern void c_routine (void);
  +
extern void haskell_definition (void);
  +
</haskell>
  +
  +
It may be compiled and linked in one step by ghc:
  +
ghc --make main.hs vile.c
  +
  +
Or, you may compile C module(s) separately and link in ".o" files (this may be preferable if you use <code>make</code> and don't want to recompile unchanged sources; ghc's <code>--make</code> option provides smart recompilation only for ".hs" files):
  +
ghc -c vile.c
  +
ghc --make main.hs vile.o
  +
  +
You may use gcc/g++ directly to compile your C/C++ files but I recommend to do linking via ghc because it adds a lot of libraries required for execution of Haskell code. For the same reason, even if <code>main</code> in your program is written in C/C++, I recommend calling it from the Haskell action <code>main</code> - otherwise you'll have to explicitly init/shutdown the GHC RTS (run-time system).
  +
  +
We use the <code>foreign import</code> declaration to import foreign routines into Haskell, and <code>foreign export</code> to export Haskell definitions "outside" for imperative languages to use. Note that <code>import</code> creates a new Haskell symbol (from the external one), while <code>export</code> uses a Haskell symbol previously defined. Technically speaking, both types of declarations create a wrapper that converts the names and calling conventions from C to Haskell or vice versa.
  +
  +
=== All about the <code>foreign</code> declaration ===
  +
  +
The <code>ccall</code> specifier in foreign declarations means the use of the C (not C++ !) calling convention. This means that if you want to write the external routine in C++ (instead of C) you should add <code>export "C"</code> specification to its declaration - otherwise you'll get linking errors. Let's rewrite our first example to use C++ instead of C:
  +
  +
''prototypes.h:''
  +
<haskell>
  +
#ifdef __cplusplus
  +
extern "C" {
  +
#endif
  +
  +
extern void c_routine (void);
  +
extern void haskell_definition (void);
  +
  +
#ifdef __cplusplus
  +
}
  +
#endif
  +
</haskell>
  +
  +
Compile it via:
  +
  +
ghc --make main.hs vile.cpp
  +
  +
where "vile.cpp" is just a renamed copy of "vile.c" from the first example. Note that the new "prototypes.h" is written to allow compiling it both as C and C++ code. When it's included from "vile.cpp", it's compiled as C++ code. When GHC compiles "main.hs" via the C compiler (enabled by the <code>-fvia-C</code> option), it also includes "prototypes.h" but compiles it in C mode. It's why you need to specify ".h" files in <code>foreign</code> declarations - depending on which Haskell compiler you use, these files may be included to check consistency of C and Haskell declarations.
  +
  +
The quoted part of the foreign declaration may also be used to give the import or export another name - for example,
  +
  +
<haskell>
  +
foreign import ccall safe "prototypes.h CRoutine"
  +
c_routine :: IO ()
  +
  +
foreign export ccall "HaskellDefinition"
  +
haskell_definition :: IO ()
  +
</haskell>
  +
  +
specifies that:
  +
* the C routine called <code>CRoutine</code> will become known as <code>c_routine</code> in Haskell,
  +
* while the Haskell definition <code>haskell_definition</code> will be known as <code>HaskellDefinition</code> in C.
  +
  +
It's required when the C name doesn't conform to Haskell naming requirements.
  +
  +
Although the Haskell FFI standard tells about many other calling conventions in addition to <code>ccall</code> (e.g. <code>cplusplus</code>, <code>jvm</code>, <code>net</code>) current Haskell implementations support only <code>ccall</code> and <code>stdcall</code>. The latter, also called the "Pascal" calling convention, is used to interface with WinAPI:
  +
  +
<haskell>
  +
foreign import stdcall unsafe "windows.h SetFileApisToOEM"
  +
setFileApisToOEM :: IO ()
  +
</haskell>
  +
  +
And finally, about the <code>safe</code>/<code>unsafe</code> specifier: a C routine imported with the <code>unsafe</code> keyword is called directly and the Haskell runtime is stopped while the C routine is executed (when there are several OS threads executing the Haskell program, only the current OS thread is delayed). This call doesn't allow recursively entering back into Haskell by calling any Haskell definition - the Haskell RTS is just not prepared for such an event. However, <code>unsafe</code> calls are as quick as calls in C. It's ideal for "momentary" calls that quickly return back to the caller.
  +
  +
When <code>safe</code> is specified, the C routine is called in a safe environment - the Haskell execution context is saved, so it's possible to call back to Haskell and, if the C call takes a long time, another OS thread may be started to execute Haskell code (of course, in threads other than the one that called the C code). This has its own price, though - around 1000 CPU ticks per call.
  +
  +
You can read more about interaction between FFI calls and Haskell concurrency in [[#readmore|[7]]].
  +
  +
=== Marshalling simple types ===
  +
  +
Calling by itself is relatively easy; the real problem of interfacing languages with different data models is passing data between them. In this case, there is no guarantee that Haskell's <code>Int</code> is represented in memory the same way as C's <code>int</code>, nor Haskell's <code>Double</code> the same as C's <code>double</code> and so on. While on ''some'' platforms they are the same and you can write throw-away programs relying on these, the goal of portability requires you to declare foreign imports and exports using special types described in the FFI standard, which are guaranteed to correspond to C types. These are:
  +
  +
<haskell>
  +
import Foreign.C.Types ( -- equivalent to the following C type:
  +
CChar, CUChar, -- char/unsigned char
  +
CShort, CUShort, -- short/unsigned short
  +
CInt, CUInt, CLong, CULong, -- int/unsigned/long/unsigned long
  +
CFloat, CDouble...) -- float/double
  +
</haskell>
  +
  +
Now we can typefully import and export to and from C and Haskell:
  +
<haskell>
  +
foreign import ccall unsafe "math.h"
  +
c_sin :: CDouble -> CDouble
  +
</haskell>
  +
  +
Note that C routines <i>which behave like pure functions</i> (those whose results depend only on their arguments) are imported without <code>IO</code> in their return type. The <code>const</code> specifier in C is not reflected in Haskell types, so appropriate compiler checks are not performed. <!-- What would these be? -->
  +
  +
All these numeric types are instances of the same classes as their Haskell cousins (<code>Ord</code>, <code>Num</code>, <code>Show</code> and so on), so you may perform calculations on these data directly. Alternatively, you may convert them to native Haskell types. It's very typical to write simple wrappers around foreign imports and exports just to provide interfaces having native Haskell types:
  +
  +
<haskell>
  +
-- |Type-conversion wrapper around c_sin
  +
sin :: Double -> Double
  +
sin = fromRational . c_sin . toRational
  +
</haskell>
  +
  +
=== Memory management ===
  +
  +
=== Marshalling strings ===
  +
  +
<haskell>
  +
import Foreign.C.String ( -- representation of strings in C
  +
CString, -- = Ptr CChar
  +
CStringLen) -- = (Ptr CChar, Int)
  +
</haskell>
  +
  +
<haskell>
  +
foreign import ccall unsafe "string.h"
  +
c_strlen :: CString -> IO CSize -- CSize defined in Foreign.C.Types and is equal to size_t
  +
</haskell>
  +
  +
<haskell>
  +
-- |Type-conversion wrapper around c_strlen
  +
strlen :: String -> Int
  +
strlen = ....
  +
</haskell>
  +
  +
=== Marshalling composite types ===
  +
  +
A C array may be manipulated in Haskell as [http://haskell.org/haskellwiki/Arrays#StorableArray_.28module_Data.Array.Storable.29 StorableArray].
  +
  +
There is no built-in support for marshalling C structures and using C constants in Haskell. These are implemented in the c2hs preprocessor, though.
  +
  +
Binary marshalling (serializing) of data structures of any complexity is implemented in the library module "Binary".
  +
  +
=== Dynamic calls ===
  +
  +
=== DLLs ===
  +
''because i don't have experience of using DLLs, can someone write into this section? Ultimately, we need to consider the following tasks:''
  +
* using DLLs of 3rd-party libraries (such as ''ziplib'')
  +
* putting your own C code into a DLL to use in Haskell
  +
* putting Haskell code into a DLL which may be called from C code
  +
  +
  +
== '''The dark side of the I/O monad''' ==
  +
  +
Unless you are a systems developer, postgraduate CS student, or have alternate (and eminent!) verifiable qualifications you should have '''no need whatsoever''' for this section - [https://stackoverflow.com/questions/9449239/unsafeperformio-in-threaded-applications-does-not-work here] is just one tiny example of what can go wrong if you don't know what you are doing. Look for other solutions!
  +
  +
=== '''unsafePerformIO''' ===
  +
Do you remember that initial attempt to define <code>getchar</code>?
  +
  +
<haskell>
  +
getchar :: Char
  +
  +
get2chars :: String
  +
get2chars = [a, b] where a = getchar
  +
b = getchar
  +
</haskell>
  +
  +
Let's also recall the problems arising from this ''faux''-definition:
  +
  +
# Because the Haskell compiler treats all functions as pure (not having side effects), it can avoid "unnecessary" calls to <code>getchar</code> and use one returned value twice;
  +
# Even if it does make two calls, there is no way to determine which call should be performed first. Do you want to return the two characters in the order in which they were read, or in the opposite order? Nothing in the definition of <code>get2chars</code> answers this question.
  +
  +
Despite these problems, programmers coming from an imperative language background often look for a way to do this - disguise one or more I/O actions as a pure definition. Having seen procedural entities similar in appearance to:
  +
  +
<haskell>
  +
void putchar(char c);
  +
</haskell>
  +
  +
the thought of just writing:
  +
  +
<haskell>
  +
putchar :: Char -> ()
  +
putchar c = ...
  +
</haskell>
  +
  +
would definitely be more appealing - for example, defining <code>readContents</code> as though it were a pure function:
   
 
<haskell>
 
<haskell>
Line 932: Line 1,247:
 
</haskell>
 
</haskell>
   
Defining readContents as a pure function will certainly simplify the code that uses it. But it will also create problems for the compiler:
+
will certainly simplify the code that uses it. However, those exact same problems are also lurking here:
   
  +
# Attempts to read the contents of files with the same name can be factored (''i.e.'' reduced to a single call) despite the fact that the file (or the current directory) can be changed between calls. Haskell considers all non-<code>IO</code> functions to be pure and feels free to merge multiple calls with the same parameters.
 
# This call is not inserted in a sequence of "world transformations", so the compiler doesn't know at what exact moment you want to execute this action. For example, if the file has one kind of contents at the beginning of the program and another at the end - which contents do you want to see? You have no idea when (or even if) this function is going to get invoked, because Haskell sees this function as pure and feels free to reorder the execution of any or all pure functions as needed.
 
# This call is not inserted in a sequence of "world transformations", so the compiler doesn't know at what exact moment you want to execute this action. For example, if the file has one kind of contents at the beginning of the program and another at the end - which contents do you want to see? You have no idea when (or even if) this function is going to get invoked, because Haskell sees this function as pure and feels free to reorder the execution of any or all pure functions as needed.
# Attempts to read the contents of files with the same name can be factored (''i.e.'' reduced to a single call) despite the fact that the file (or the current directory) can be changed between calls. Again, Haskell considers all non-IO functions to be pure and feels free to omit multiple calls with the same parameters.
 
   
So, implementing pure functions that interact with the Real World is
+
So, implementing supposedly-pure functions that interact with the '''Real World''' is considered to be '''Bad Behavior'''. Nice programmers never do it ;-)
considered to be Bad Behavior. Good boys and girls never do it ;)
 
   
  +
Nevertheless, there are (semi-official) ways to use I/O actions inside of pure functions. As you should remember this is prohibited by requiring the <code>RealWorld</code> "baton" in order to call an I/O action. Pure functions don't have the baton, but there is a ''(ahem)'' "special" definition that produces this baton from nowhere, uses it to call an I/O action and then throws the resulting "world" away! It's a little low-level mirror-smoke. This particular (and dangerous) definition is:
 
Nevertheless, there are (semi-official) ways to use IO actions inside
 
of pure functions. As you should remember this is prohibited by
 
requiring the RealWorld "baton" in order to call an IO action. Pure functions don't have the baton, but there is a special "magic" procedure that produces this baton from nowhere, uses it to call an IO action and then throws the resulting "world" away! It's a little low-level magic :) This very special (and dangerous) procedure is:
 
   
 
<haskell>
 
<haskell>
Line 949: Line 1,260:
 
</haskell>
 
</haskell>
   
Let's look at its (possible) definition:
+
Let's look at how it ''could'' be defined:
   
 
<haskell>
 
<haskell>
Line 957: Line 1,268:
 
</haskell>
 
</haskell>
   
where 'createNewWorld' is an internal function producing a new value of
+
where <code>createNewWorld</code> is an private definition producing a new value of the <code>RealWorld</code> type.
the RealWorld type.
 
   
Using unsafePerformIO, you can easily write pure functions that do
+
Using <code>unsafePerformIO</code>, you could easily write "pure-looking functions" that actually do I/O inside. But don't do this without a real need, and remember to follow this rule:
I/O inside. But don't do this without a real need, and remember to
 
follow this rule: the compiler doesn't know that you are cheating; it still
 
considers each non-IO function to be a pure one. Therefore, all the usual
 
optimization rules can (and will!) be applied to its execution. So
 
you must ensure that:
 
   
  +
* the compiler doesn't know that you are cheating; it still considers each non-<code>IO</code> function to be a pure one. Therefore, all the usual optimization rules can (and will!) be applied to its execution.
# The result of each call depends only on its arguments.
 
# You don't rely on side-effects of this function, which may be not executed if its results are not needed.
 
   
  +
So you must ensure that:
   
  +
* The result of each call depends only on its arguments.
Let's investigate this problem more deeply. Function evaluation in Haskell
 
  +
* You don't rely on side-effects of this function, which may be not executed if its results are not needed.
is determined by a value's necessity - the language computes only the values that are really required to calculate the final result. But what does this mean with respect to the 'main' function? To "calculate the final world's" value, you need to perform all the intermediate IO actions that are included in the 'main' chain. By using 'unsafePerformIO' we call IO actions outside of this chain. What guarantee do we have that they will be run at all? None. The only time they will be run is if running them is required to compute the overall function result (which in turn should be required to perform some action in the
 
'main' chain). This is an example of Haskell's evaluation-by-need strategy. Now you should clearly see the difference:
 
   
  +
Let's investigate this problem more deeply. Function evaluation in Haskell is determined by a value's necessity - the language computes only the values that are really required to calculate the final result. But what does this mean with respect to the <code>main</code> action? To "calculate the final world's" value, you need to perform all the intermediate I/O actions that are included in the <code>main</code> chain. By using <code>unsafePerformIO</code> we call I/O actions outside of this chain. What guarantee do we have that they will be run at all? None. The only time they will be run is if running them is required to compute the overall function result (which in turn should be required to perform some action in the <code>main</code> chain). This is an example of Haskell's evaluation-by-need strategy. Now you should clearly see the difference:
- An IO action inside an IO procedure is guaranteed to execute as long as
 
it is (directly or indirectly) inside the 'main' chain - even when its result isn't used (because the implicit "world" value it returns ''will'' be used). You directly specify the order of the action's execution inside the IO procedure. Data dependencies are simulated via the implicit "world" values that are passed from each IO action to the next.
 
   
  +
* An I/O action inside an I/O definition is guaranteed to execute as long as it is (directly or indirectly) inside the <code>main</code> chain - even when its result isn't used (because the implicit "world" value it returns ''will'' be used). You directly specify the order of the action's execution inside the I/O definition. Data dependencies are simulated via the implicit "world" values that are passed from each I/O action to the next.
- An IO action inside 'unsafePerformIO' will be performed only if
 
result of this operation is really used. The evaluation order is not
 
guaranteed and you should not rely on it (except when you're sure about
 
whatever data dependencies may exist).
 
   
  +
* An I/O action inside <code>unsafePerformIO</code> will be performed only if the result of this operation is really used. The evaluation order is not guaranteed and you should not rely on it (except when you're sure about whatever data dependencies may exist).
   
  +
I should also say that inside the <code>unsafePerformIO</code> call you can organize a small internal chain of I/O actions with the help of the same binding operators and/or <code>do</code> syntactic sugar we've seen above. So here's how we'd rewrite our previous (pure!) definition of <code>one</code> using <code>unsafePerformIO</code>:
I should also say that inside 'unsafePerformIO' call you can organize
 
a small internal chain of IO actions with the help of the same binding
 
operators and/or 'do' syntactic sugar we've seen above. For example, here's a particularly convoluted way to compute the integer that comes after zero:
 
   
 
<haskell>
 
<haskell>
one :: Int
+
one :: Integer
 
one = unsafePerformIO $ do var <- newIORef 0
 
one = unsafePerformIO $ do var <- newIORef 0
 
modifyIORef var (+1)
 
modifyIORef var (+1)
Line 995: Line 1,294:
 
</haskell>
 
</haskell>
   
and in this case ALL the operations in this chain will be performed as
+
and in this case ''all'' the operations in this chain will be performed as long as the result of the <code>unsafePerformIO</code> call is needed. To ensure this, the actual <code>unsafePerformIO</code> implementation evaluates the "world" returned by the <code>action</code>:
long as the result of the 'unsafePerformIO' call is needed. To ensure this,
 
the actual 'unsafePerformIO' implementation evaluates the "world" returned
 
by the 'action':
 
 
 
<haskell>
 
<haskell>
 
unsafePerformIO action = let (a,world1) = action createNewWorld
 
unsafePerformIO action = let (a,world1) = action createNewWorld
Line 1,005: Line 1,300:
 
</haskell>
 
</haskell>
   
(The 'seq' operation strictly evaluates its first argument before
+
(The <code>seq</code> operation strictly evaluates its first argument before
returning the value of the second one).
+
returning the value of the second one [[#readmore|[8]]]).
   
  +
=== '''inlinePerformIO''' ===
   
  +
<code>inlinePerformIO</code> has the same definition as <code>unsafePerformIO</code> but with the addition of an <code>INLINE</code> pragma:
=== inlinePerformIO ===
 
 
inlinePerformIO has the same definition as unsafePerformIO but with addition of INLINE pragma:
 
 
<haskell>
 
<haskell>
 
-- | Just like unsafePerformIO, but we inline it. Big performance gains as
 
-- | Just like unsafePerformIO, but we inline it. Big performance gains as
Line 1,018: Line 1,312:
 
inlinePerformIO action = let (a, world1) = action createNewWorld
 
inlinePerformIO action = let (a, world1) = action createNewWorld
 
in (world1 `seq` a)
 
in (world1 `seq` a)
#endif
 
 
</haskell>
 
</haskell>
   
Semantically inlinePerformIO = unsafePerformIO
+
Semantically <code>inlinePerformIO</code> = <code>unsafePerformIO</code> in as much as either of those have any semantics at all.
in as much as either of those have any semantics at all.
 
   
  +
The difference of course is that <code>inlinePerformIO</code> is even less safe than <code>unsafePerformIO</code>. While ghc will try not to duplicate or common up different uses of <code>unsafePerformIO</code>, we aggressively inline <code>inlinePerformIO</code>. So you can really only use it where the I/O content is really properly pure, like reading from an immutable memory buffer (as in the case of <code>ByteString</code>s). However things like allocating new buffers should not be done inside <code>inlinePerformIO</code> since that can easily be floated out and performed just once for the whole program, so you end up with many things sharing the same buffer, which would be bad.
The difference of course is that inlinePerformIO is even less safe than
 
unsafePerformIO. While ghc will try not to duplicate or common up
 
different uses of unsafePerformIO, we aggressively inline
 
inlinePerformIO. So you can really only use it where the IO content is
 
really properly pure, like reading from an immutable memory buffer (as
 
in the case of ByteStrings). However things like allocating new buffers
 
should not be done inside inlinePerformIO since that can easily be
 
floated out and performed just once for the whole program, so you end up
 
with many things sharing the same buffer, which would be bad.
 
   
So the rule of thumb is that IO things wrapped in unsafePerformIO have
+
So the rule of thumb is that I/O actions wrapped in <code>unsafePerformIO</code> have to be externally pure while with <code>inlinePerformIO</code> it has to be really, ''really'' pure or it'll all go horribly wrong.
to be externally pure while with inlinePerformIO it has to be really
 
really pure or it'll all go horribly wrong.
 
   
That said, here's some really hairy code. This should frighten any pure
+
That said, here's some really hairy code. This should frighten any pure functional programmer...
functional programmer...
 
   
 
<haskell>
 
<haskell>
Line 1,045: Line 1,326:
 
write !n body = Put $ \c buf@(Buffer fp o u l) ->
 
write !n body = Put $ \c buf@(Buffer fp o u l) ->
 
if n <= l
 
if n <= l
then write' c fp o u l
+
then write</code> c fp o u l
else write' (flushOld c n fp o u) (newBuffer c n) 0 0 0
+
else write</code> (flushOld c n fp o u) (newBuffer c n) 0 0 0
   
where {-# NOINLINE write' #-}
+
where {-# NOINLINE write</code> #-}
write' c !fp !o !u !l =
+
write</code> c !fp !o !u !l =
 
-- warning: this is a tad hardcore
 
-- warning: this is a tad hardcore
 
inlinePerformIO
 
inlinePerformIO
Line 1,062: Line 1,343:
 
</haskell>
 
</haskell>
   
This does not adhere to my rule of thumb above. Don't ask exactly why we
+
This does not adhere to my rule of thumb above. Don't ask exactly why we claim it's safe :-) (and if anyone really wants to know, ask Ross Paterson who did it first in the <code>Builder</code> monoid)
claim it's safe :-) (and if anyone really wants to know, ask Ross
 
Paterson who did it first in the Builder monoid)
 
   
=== unsafeInterleaveIO ===
+
=== '''unsafeInterleaveIO''' ===
   
But there is an even stranger operation called 'unsafeInterleaveIO' that
+
But there is an even stranger operation:
gets the "official baton", makes its own pirate copy, and then runs
 
an "illegal" relay-race in parallel with the main one! I can't talk further
 
about its behavior without causing grief and indignation, so it's no surprise
 
that this operation is widely used in countries that are hotbeds of software piracy such as Russia and China! ;) Don't even ask me - I won't say anything more about this dirty trick I use all the time ;)
 
   
  +
<haskell>
One can use unsafePerformIO (not unsafeInterleaveIO) to perform I/O
 
  +
unsafeInterleaveIO :: IO a -> IO a
operations not in predefined order but by demand. For example, the
 
  +
</haskell>
following code:
 
  +
  +
Don't let that type signature fool you - <code>unsafeInterleaveIO</code> also uses a dubiously-acquired baton which it uses to set up an underground relay-race for its unsuspecting parameter. If it happens, this seedy race then occurs alongside the offical <code>main</code> relay-race - if they collide, things will get ugly!
  +
  +
So how does <code>unsafeInterleaveIO</code> get that bootlegged baton? Typically by making a forgery of the offical one to keep for itself - it can do this because the I/O action <code>unsafeInterleaveIO</code> returns will be handed the offical baton in the <code>main</code> relay-race. But one miscreant realised there was a simpler way:
  +
  +
<haskell>
  +
{-# NOINLINE unsafeInterleaveIO #-}
  +
unsafeInterleaveIO :: IO a -> IO a
  +
unsafeInterleaveIO a = return (unsafePerformIO a)
  +
</haskell>
  +
  +
Why bother with counterfeit copies of batons if you can just make them up?
  +
  +
At least you have some appreciation as to why <code>unsafeInterleaveIO</code> is, well '''unsafe!''' Just don't ask - to talk further is bound to cause grief and indignation. I won't say anything more about this ruffian I...use all the time (darn it!)
  +
  +
One can use <code>unsafePerformIO</code> (not <code>unsafeInterleaveIO</code>) to perform I/O operations not in some predefined order but by demand. For example, the following code:
   
 
<haskell>
 
<haskell>
Line 1,083: Line 1,374:
 
</haskell>
 
</haskell>
   
will perform getChar I/O call only when value of c is really required
+
will perform the <code>getChar</code> I/O call only when the value of <code>c</code> is really required by the calling code, i.e. it this call will be performed lazily like any regular Haskell computation.
by code, i.e. it this call will be performed lazily as any usual
 
Haskell computation.
 
   
 
Now imagine the following code:
 
Now imagine the following code:
Line 1,094: Line 1,383:
 
</haskell>
 
</haskell>
   
Three chars inside this list will be computed on demand too, and this
+
The three characters inside this list will be computed on demand too, and this means that their values will depend on the order they are consumed. It is not what we usually want.
means that their values will depend on the order they are consumed. It
 
is not that we usually need :)
 
   
  +
<code>unsafeInterleaveIO</code> solves this problem - it performs I/O only on demand but allows you to define the exact ''internal'' execution order for parts of your data structure. It is why I wrote that <code>unsafeInterleaveIO</code> makes an illegal copy of the baton:
   
unsafeInterleaveIO solves this problem - it performs I/O only on
+
* <code>unsafeInterleaveIO</code> accepts an I/O action as a parameter and returns another I/O action as the result:
demand but allows to define exact *internal* execution order for parts
 
of your datastructure. It is why I wrote that unsafeInterleaveIO makes
 
illegal copy of baton :)
 
   
  +
:<haskell>
First, unsafeInterleaveIO has (IO a) action as a parameter and returns
 
value of type 'a':
 
 
<haskell>
 
 
do str <- unsafeInterleaveIO myGetContents
 
do str <- unsafeInterleaveIO myGetContents
  +
 
</haskell>
 
</haskell>
   
Second, unsafeInterleaveIO don't perform any action immediately, it
+
* <code>unsafeInterleaveIO</code> doesn't perform any action immediately, it only creates a closure of type <code>a</code> which upon being needed will perform the action specified as the parameter.
only creates a box of type 'a' which on requesting this value will
 
perform action specified as a parameter.
 
   
Third, this action by itself may compute the whole value immediately
+
* this action by itself may compute the whole value immediately...or use <code>unsafeInterleaveIO</code> again to defer calculation of some sub-components:
or... use unsafeInterleaveIO again to defer calculation of some
 
sub-components:
 
   
<haskell>
+
:<haskell>
 
myGetContents = do
 
myGetContents = do
 
c <- getChar
 
c <- getChar
Line 1,126: Line 1,405:
 
</haskell>
 
</haskell>
   
  +
This code will be executed only at the moment when the value of <code>str</code> is really demanded. In this moment, <code>getChar</code> will be performed (with its result assigned to <code>c</code>) and a new lazy-I/O closure will be created - for <code>s</code>. This new closure also contains a link to a <code>myGetContents</code> call.
This code will be executed only at the moment when value of str is
 
really demanded. In this moment, getChar will be performed (with
 
result assigned to c) and one more lazy IO box will be created - for s.
 
This box again contains link to the myGetContents call
 
   
  +
The resulting list is then returned. It contains the <code>Char</code> that was just read and a link to another <code>myGetContents</code> call as a way to compute the rest of the list. Only at the moment when the next value in the list is required will this operation be performed again.
Then, list cell returned that contains one char read and link to
 
myGetContents call as a way to compute rest of the list. Only at the
 
moment when next value in list required, this operation will be
 
performed again
 
   
As a final result, we get inability to read second char in list before
+
As a final result, we can postpone the read of the second <code>Char</code> in the list before the first one, but have lazy reading of characters as a whole - bingo!
first one, but lazy character of reading in whole. bingo!
 
   
   
PS: of course, actual code should include EOF checking. also note that
+
PS: of course, actual code should include EOF checking; also note that you can read multiple characters/records at each call:
you can read many chars/records at each call:
 
   
 
<haskell>
 
<haskell>
 
myGetContents = do
 
myGetContents = do
c <- replicateM 512 getChar
+
l <- replicateM 512 getChar
 
s <- unsafeInterleaveIO myGetContents
 
s <- unsafeInterleaveIO myGetContents
return (c++s)
+
return (l++s)
 
</haskell>
 
</haskell>
  +
  +
and we can rewrite <code>myGetContents</code> to avoid needing to use <code>unsafeInterleaveIO</code> where it's called:
  +
  +
<haskell>
  +
myGetContents = unsafeInterleaveIO $ do
  +
l <- replicateM 512 getChar
  +
s <- myGetContents
  +
return (l++s)
  +
</haskell>
  +
   
 
== Welcome to the machine: the actual [[GHC]] implementation ==
 
== Welcome to the machine: the actual [[GHC]] implementation ==
   
  +
A little disclaimer: I should say that I'm not describing here exactly what a monad is (I don't even completely understand it myself) and my explanation shows only one ''possible'' way to implement the I/O monad in Haskell. For example, the hbc compiler and the Hugs interpreter implements the I/O monad via continuations [[#readmore|[9]]]. I also haven't said anything about exception handling, which is a natural part of the "monad" concept. You can read the [[All About Monads]] guide to learn more about these topics.
A little disclaimer: I should say that I'm not describing
 
here exactly what a monad is (I don't even completely understand it myself) and my explanation shows only one _possible_ way to implement the IO monad in
 
Haskell. For example, the hbc Haskell compiler implements IO monad via
 
continuations. I also haven't said anything about exception handling,
 
which is a natural part of the "monad" concept. You can read the "All About
 
Monads" guide to learn more about these topics.
 
   
  +
But there is some good news:
But there is some good news: first, the IO monad understanding you've just acquired will work with any implementation and with many other monads. You just can't work with RealWorld
 
values directly.
 
   
  +
* the I/O monad understanding you've just acquired will work with any implementation and with many other monads. You just can't work with <code>RealWorld</code> values directly.
Second, the IO monad implementation described here is really used in the GHC,
 
yhc/nhc (Hugs/jhc, too?) compilers. Here is the actual IO definition
 
from the GHC sources:
 
   
  +
* the I/O monad implementation described here is similar to what GHC uses:
<haskell>
 
  +
:<haskell>
 
newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
 
newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
 
</haskell>
 
</haskell>
   
It uses the "State# RealWorld" type instead of our RealWorld, it uses the "(# #)" strict tuple for optimization, and it adds an IO data constructor
+
It uses the <code>State# RealWorld</code> type instead of our <code>RealWorld</code>, it uses the <code>(# ... #)</code> strict tuple for optimization, and it uses an <code>IO</code> data constructor instead of our <code>Act</code>. Nevertheless, there are no significant changes from the standpoint of our explanation. Knowing the principle of "chaining" I/O actions via fake "state of the world" values, you can now more easily understand and write low-level implementations of GHC I/O operations.
around the type. Nevertheless, there are no significant changes from the standpoint of our explanation. Knowing the principle of "chaining" IO actions via fake "state of the world" values, you can now easily understand and write low-level implementations of GHC I/O operations.
 
   
  +
Of course, other compilers e.g. yhc/nhc (jhc, too?) define <code>IO</code> in other ways.
   
 
=== The [[Yhc]]/nhc98 implementation ===
 
=== The [[Yhc]]/nhc98 implementation ===
Line 1,181: Line 1,455:
 
</haskell>
 
</haskell>
   
  +
This implementation makes the <code>World</code> disappear somewhat[[#readmore|[10]]], and returns <code>Either</code> a result of type <code>a</code>, or if an error occurs then <code>IOError</code>. The lack of the <code>World</code> on the right-hand side of the function can only be done because the compiler knows special things about the <code>IO</code> type, and won't overoptimise it.
This implementation makes the "World" disappear somewhat, and returns Either a
 
result of type "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 won't overoptimise it.
 
   
   
== Further reading ==
+
== <span id="readmore"></span>Further reading ==
   
This tutorial is largely based on the Simon Peyton Jones' paper [http://research.microsoft.com/%7Esimonpj/Papers/marktoberdorf Tackling the awkward squad: monadic input/output, concurrency, exceptions, and foreign-language calls in Haskell]. I hope that my tutorial improves his original explanation of the Haskell I/O system and brings it closer to the point of view of beginning Haskell programmers. But if you need to learn about concurrency, exceptions and FFI in Haskell/GHC, the original paper is the best source of information.
+
[1] This tutorial is largely based on Simon Peyton Jones's paper [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.13.9123&rep=rep1&type=pdf Tackling the awkward squad: monadic input/output, concurrency, exceptions, and foreign-language calls in Haskell]. I hope that my tutorial improves his original explanation of the Haskell I/O system and brings it closer to the point of view of new Haskell programmers. But if you need to learn about concurrency, exceptions and the FFI in Haskell/GHC, the original paper is the best source of information.
   
You can find more information about concurrency, FFI and STM at the [[GHC/Concurrency#Starting points]] page.
+
[2] You can find more information about concurrency, the FFI and STM at the [[GHC/Concurrency#Starting points]] page.
   
The [[Arrays]] page contains exhaustive explanations about using mutable arrays.
+
[3] The [[Arrays]] page contains exhaustive explanations about using mutable arrays.
   
Look also at the [[Books and tutorials#Using Monads]] page, which contains tutorials and papers really describing these mysterious monads :)
+
[4] Look also at the [[Tutorials#Using_monads|Using monads]] page, which contains tutorials and papers really describing these mysterious monads.
   
An explanation of the basic monad functions, with examples, can be found in the reference guide [http://members.chello.nl/hjgtuyl/tourdemonad.html A tour of the Haskell Monad functions], by Henk-Jan van Tuyl.
+
[5] An explanation of the basic monad functions, with examples, can be found in the reference guide [https://web.archive.org/web/20201109033750/members.chello.nl/hjgtuyl/tourdemonad.html A tour of the Haskell Monad functions], by Henk-Jan van Tuyl.
   
  +
[6] Official FFI specifications can be found on the page [http://www.cse.unsw.edu.au/~chak/haskell/ffi/ The Haskell 98 Foreign Function Interface 1.0: An Addendum to the Haskell 98 Report]
Do you have more questions? Ask in the [http://www.haskell.org/mailman/listinfo/haskell-cafe haskell-cafe mailing list].
 
   
  +
[7] Using the FFI in multithreaded programs is described in [http://www.haskell.org/~simonmar/bib/concffi04_abstract.html Extending the Haskell Foreign Function Interface with Concurrency]
  +
  +
[8] This particular behaviour is not a requirement of Haskell 2010, so the operation of <code>seq</code> may differ between various Haskell implementations - if you're not sure, staying within the I/O monad is the safest option.
  +
  +
[9] [http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf How to Declare an Imperative] by Phil Wadler provides an explanation of how this can be done.
  +
  +
[10] The <code>RealWorld</code> type can even be replaced e.g. <span style="color:darkred;">Functional I/O Using System Tokens</span> by Lennart Augustsson.
  +
  +
Do you have more questions? Ask in the [http://www.haskell.org/mailman/listinfo/haskell-cafe haskell-cafe mailing list].
   
 
== To-do list ==
 
== To-do list ==
Line 1,205: Line 1,487:
   
 
Topics:
 
Topics:
* fixIO and 'mdo'
+
* <code>fixIO</code> and <code>mdo</code>
* ST monad
+
* <code>Q</code> monad
* Q monad
 
   
 
Questions:
 
Questions:
* split '>>='/'>>'/return section and 'do' section, more examples of using binding operators
+
* split <code>(>>=)</code>/<code>(>>)</code>/<code>return</code> section and <code>do</code> section, more examples of using binding operators
* IORef detailed explanation (==const*), usage examples, syntax sugar, unboxed refs
+
* <code>IORef</code> detailed explanation (==<code>const*</code>), usage examples, syntax sugar, unboxed refs
  +
* explanation of how the actual data "in" mutable references are inside <code>RealWorld</code>, rather than inside the references themselves (<code>IORef</code>, <code>IOArray</code> & co.)
 
* control structures developing - much more examples
 
* control structures developing - much more examples
* unsafePerformIO usage examples: global variable, ByteString, other examples
+
* <code>unsafePerformIO</code> usage examples: global variable, <code>ByteString</code>, other examples
  +
* how <code>unsafeInterLeaveIO</code> can be seen as a kind of concurrency, and therefore isn't so unsafe (unlike <code>unsafeInterleaveST</code> which really is unsafe)
* actual GHC implementation - how to write low-level routines on example of newIORef implementation
 
  +
* discussion about different senses of <code>safe</code>/<code>unsafe</code> (like breaking equational reasoning vs. invoking undefined behaviour (so can corrupt the run-time system))
  +
* actual GHC implementation - how to write low-level definitions based on example of <code>newIORef</code>'s implementation
   
This manual is collective work, so feel free to add more information to it yourself. The final goal is to collectively develop a comprehensive manual for using the IO monad.
+
This manual is collective work, so feel free to add more information to it yourself. The final goal is to collectively develop a comprehensive manual for using the I/O monad.
   
 
----
 
----

Latest revision as of 12:00, 21 July 2023

Haskell I/O can be a source of confusion and surprises for new Haskellers - if that's you, a good place to start is the Introduction to IO which can help you learn the basics (e.g. the syntax of I/O expressions) before continuing on.


While simple I/O code in Haskell looks very similar to its equivalents in imperative languages, attempts to write somewhat more complex code often result in a total mess. This is because Haskell I/O is really very different in how it actually works.

The following text is an attempt to explain the details of Haskell I/O implementations. This explanation should help you eventually learn all the smart I/O tips. Moreover, I've added a detailed explanation of various traps you might encounter along the way. After reading this text, you will be well on your way towards mastering I/O in Haskell.


Haskell is a pure language

Haskell is a pure language and even the I/O system can't break this purity. Being pure means that the result of any function call is fully determined by its arguments. Imperative routines like rand() or getchar() in C, which return different results on each call, are simply impossible to write in Haskell. Moreover, Haskell functions can't have side effects, which means that they can't make any changes "outside the Haskell program", like changing files, writing to the screen, printing, sending data over the network, and so on. These two restrictions together mean that any function call can be replaced by the result of a previous call with the same parameters, and the language guarantees that all these rearrangements will not change the program result! For example, the hyperbolic cosine function cosh can be defined in Haskell as:

cosh r = (exp r + 1/exp r)/2

using identical calls to exp, which is another function. So cosh can instead call exp once, and reuse the result:

cosh r = (x + 1/x)/2 where x = exp r

Let's compare this to C: optimizing C compilers try to guess which routines have no side effects and don't depend on mutable global variables. If this guess is wrong, an optimization can change the program's semantics! To avoid this kind of disaster, C optimizers are conservative in their guesses or require hints from the programmer about the purity of routines.

Compared to an optimizing C compiler, a Haskell compiler is a set of pure mathematical transformations. This results in much better high-level optimization facilities. Moreover, pure mathematical computations can be much more easily divided into several threads that may be executed in parallel, which is increasingly important in these days of multi-core CPUs. Finally, pure computations are less error-prone and easier to verify, which adds to Haskell's robustness and to the speed of program development using Haskell.

Haskell's purity allows the compiler to call only functions whose results are really required to calculate the final value of a top-level definition (e.g. main) - this is called lazy evaluation. It's a great thing for pure mathematical computations, but how about I/O actions? Something like

putStrLn "Press any key to begin formatting"

can't return any meaningful result value, so how can we ensure that the compiler will not omit or reorder its execution? And in general: How we can work with stateful algorithms and side effects in an entirely lazy language? This question has had many different solutions proposed while Haskell was developed (see History of Haskell), with one solution eventually making its way into the current standard.


I/O in Haskell, simplified

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

getchar :: Char

get2chars :: String
get2chars = [a, b] where a = getchar
                         b = getchar

What will we get with getchar having just the Char type? You can see one problem in the definition of get2chars immediately:

  • because the Haskell compiler treats all definitions as pure (not having side effects), it can avoid "unnecessary" calls to getchar and use one returned value twice:
get2chars :: String
get2chars = [x, x] where x = getchar  -- this should be a legitimate optimisation!

How can this problem be solved from the programmer's perspective? Let's introduce a fake parameter of getchar to make each call "different" from the compiler's point of view:

getchar :: Int -> Char

get2chars :: String
get2chars = [a, b] where a = getchar 1
                         b = getchar 2

That solves the first problem mentioned above - now the compiler will make two calls because it sees that the calls have different parameters. So a single call to getchar should be even easier:

now_or_later :: String
now_or_later = case getchar 0 of
                 c | c == 'y' -> "Now"
                   | c == 'Y' -> "Now"
                 _            -> "Later"

...or not - depending on when the program is running (and how interested the user is :-) getchar 0 could equal:

  • 'y'
  • 'Y'
  • or some other character: ouch!

A matter of time

The problem is that while getchar looks like a function, it breaks one of the rules of being a function:

  • if a function's result changes, it should be because it's arguments have changed.

Instead of arbitrary Int values, what about using a ever-changing quantity as the input to getchar...like time? We just need to modify get2chars and now_or_later accordingly:

getchar :: Time -> Char

get2chars :: (Time, Time) -> String
get2chars (t1, t2) = [a, b] where a = getchar t1
                                  b = getchar t2

now_or_later :: Time -> String
now_or_later t = case getchar t of
                   c | c == 'y' -> "Now"
                     | c == 'Y' -> "Now"
                   _            -> "Later"

Now the result of calling getchar is free to change along with its input, irrespective of when the user runs the program.

Time after time

Unlike getchar and now_or_later, calling get2chars is somewhat annoying - it requires a pair of Time values, which presents a new problem. If t1 is less than t2, then:

  • should get2chars (t1, t2) == reverse (get2chars (t2, t1))?
  • or should get2chars (t2, t1) be invalid?

We can't just "snap" Time values into two "pieces", one for each getchar call:

timeSnaps :: Time -> (Time, Time)  -- ?!

so we'll just arrange for getchar to return its "completion time" along with the received input character:

getchar :: {- starting -} Time -> (Char, {- completion -} Time)

now_or_later :: Time -> String
now_or_later t1 = case getchar t1 of
                    (c, _) | c == 'y' -> "Now"
                           | c == 'Y' -> "Now"
                    _                 -> "Later

That "completion time" can then be used as the "starting time" for another getchar call:

get2chars :: Time -> String
get2chars t1 = [a, b] where (a, t2) = getchar t1
                            (b, _)  = getchar t2

with the added benefit of ordering those calls...but not calls to get2chars or now_or_later. Fortunately, this is simple to resolve - from now on, all of our I/O definitions will have "completion times":

getchar :: Time -> (Char, Time)

get2chars :: Time -> (String, Time)
get2chars t1 = ([a, b], t3) where (a, t2) = getchar t1
                                  (b, t3) = getchar t2

now_or_later :: Time -> (String, Time)
now_or_later t1 = case getchar t1 of
                    (c, t2) | c == 'y'  -> ("Now",   t2)
                            | c == 'Y'  -> ("Now",   t2)
                            | otherwise -> ("Later", t2)

The fun of plumbing

Solving one problem now leads to another:

get2chars :: Time -> (String, Time)
get2chars t1 = ([a, b], t3) where (a, t2) = getchar t3  -- this might take
                                  (b, t3) = getchar t2  --    a while...

The cause of both problems is the same: the manual manoveuring of those extra intermediate values between the definitions which use them. We need some way to automate this tedium...

Enter the monad

But what is a monad? For Haskell, it's a three-way partnership between:

  • a type: M a
  • an operator unit(M) :: a -> M a
  • an operator bind(M) :: M a -> (a -> M b) -> M b

where unit(M) and bind(M) satisfy the monad laws.

As an actual Haskell declaration:

class Monad m where
    return :: a -> m a                  -- "unit"
    (>>=)  :: m a -> (a -> m b) -> m b  -- "bind"

So how does something so vague abstract help us with I/O? Because this abstraction allows us to hide the manipulation of those irksome intermediate values! We start by modifying get2chars and now_or_later to make the use of intermediate values more visible:

get2chars    = \t1 -> let (a, t2) = getchar t1 in
                      let (b, t3) = getchar t2 in
                      let r       = [a, b] in
                      (r, t3)

now_or_later = \t1 -> let (c, t2) = getchar t1 in
                      let r = if elem c "yY" then "Now" else "Later" in
                      (r, t2)

With a suitable type:

data IO a =  Act (Time -> (a, Time))

getchar   :: IO Char

and an appropriate Monad instance:

instance Monad IO where
    m >>= k  = let actual (Act m) = m in
               Act $ \t1 -> case actual m t1 of (x, t2) -> actual (k x) t2
    return x = Act $ \t1 -> (x, t1)

we can define get2chars and now_or_later using the Monad methods:

get2chars :: IO String
get2chars =  getchar >>= \a ->
             getchar >>= \b ->
             return [a, b]

now_or_later :: IO String
now_or_later = getchar >>= \c ->
               return (if elem c "yY" then "Now" else "Later")

No more manually mangling managing intermediate values! We just need to be sure that our chosen I/O operations - getchar and the the Monad methods - use them correctly. This allows IO to be made into an abstract data type:

data IO
getchar :: IO Char
return  :: a -> IO a
(>>=)   :: IO a -> (a -> IO b) -> IO b

Now only the Haskell implementation (e.g. compilers like ghc or jhc) needs to know how I/O actions actually work.

So there you have it - a miniature monadic I/O system in Haskell!

Beyond time

We could define Time as a regular Haskell type:

data Time = Now Double

However we've been conveniently ignoring some other details:

  • For simplicity, we've only dealt with one primitive I/O action in our miniature I/O system - getchar :: IO Char. Clearly there's more to I/O than just reading in characters!
  • Programs can have more than one user:
  • If one presses 'y',
  • another presses 'n',
  • the rest press the space bar: ,
at exactly the same time - what should the result of getchar be equal to then?
We could try to avoid that problem by measuring time down to the nearest millisecond, microsecond, nanosecond, etc - however, these days humans aren't the only users: a program can also use another program. It's happening right now in the operating system running on your computer.


So what should replace those Time values? It would be futile to try defining a regular Haskell type which can work for all possible outside interactions. So the only practical choice is to use another abstract type:

data RealWorld

newtype IO a = Act (RealWorld -> (a, RealWorld))


Running with the RealWorld

Warning: The following story about I/O is incorrect in that it cannot actually explain some important aspects of I/O (including interaction and concurrency). However, some people find it useful to begin developing an understanding.

From our definition of the IO type, we can see that the RealWorld is used like the baton passed in a relay race. When an I/O action is called, it passes the RealWorld it received as a parameter. All I/O actions have similar types involving RealWorld as a parameter and result.

So, main just has type IO (), getChar has type IO Char and so on. You can think of the type IO Char as meaning "take the current RealWorld, do something to it, and return a Char and a (possibly changed) RealWorld". Let's look at main calling getChar two times:

getChar :: IO Char

main :: IO ()
main = getChar >>= \a ->
       getChar >>= \b ->
       return ()

Remember how we changed the IO type to use a newtype declaration? That decision now allows us to rewrite main as:

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 the "world" it received to the first getChar. This getChar returns some new value of type RealWorld that gets used in the next call. Finally, main returns the "world" it got from the second getChar.

  • Is it possible here to omit any call of getChar if the Char it read is not used? No: we need to return the "world" that is the result of the second getChar and this in turn requires the "world" returned from the first getChar.
  • Is it possible to reorder the getChar calls? No: the second getChar can't be called before the first one because it uses the "world" returned from the first call.
  • 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 are used like a baton which gets passed between all actions called by main in strict order. Inside each action called, RealWorld values are used in the same way. Overall, in order to "compute" the world to be returned from main, we should perform each I/O action that is called from main, directly or indirectly. This means that each action inserted in the chain will be performed just at the moment (relative to the other I/O actions) when we intended it to be called. Let's 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 a low-level way and check that each operation that should be performed will really be performed with the arguments it should have and in the order we expect.

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

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

Now to simplify it:

when condition action world =
    if condition
      then action world
      else ((), world)

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

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

Finally, you may want to know how much passing these RealWorld values around the program costs. It's free! These fake values exist solely for the compiler while it analyzes and optimizes the code, but when it gets to assembly code generation, it notices that RealWorld is like () - it contains no actual information - so all those RealWorld parameters and result values can be omitted from the final generated code: they're not needed any more!


(>>=) and do notation

All beginners (including me) start by thinking that do is some super-awesome statement that executes I/O actions. That's wrong - do is just syntactic sugar that simplifies the writing of definitions that use I/O (and also other monads, but that's beyond the scope of this tutorial). do notation eventually gets translated to a series of I/O actions passing "world" values around like we've manually written above. This simplifies the gluing of several I/O actions together. You don't need to use do for just one action; for example,

main = do putStr "Hello!"

is desugared to:

main = putStr "Hello!"

Let's examine how to desugar a do-expression with multiple actions in the following example:

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

The do-expression here just joins several I/O actions that should be performed sequentially. It's translated to sequential applications of one of the so-called "binding operators", namely (>>):

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

Defining (>>) looks easy:

(>>) :: IO a -> IO b -> IO b
action1 >> action2 = action1 >>= \_ -> action2

But if we simplify this binding operator, we can see it combining its two I/O actions, executing them sequentially by passing the "world" between them:

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

If defining operators this way looks strange to you, read this definition as follows:

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

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

A more complex example involves the binding of variables using <-:

main = do a <- readLn
          print a

This code is desugared into:

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

where (>>=) corresponds to the bind operation in our miniature I/O system.

As you should remember, the (>>) binding operator silently ignores the value of its first action and returns as an overall result the result of its second action only. On the other hand, the (>>=) binding operator (note the extra = at the end) allows us to use the result of its first action - it gets passed as an additional parameter to the second one! Let's simplify its definition:

(action >>= reaction) world0 =
   let (a, world1) = action world0
       (b, world2) = reaction a world1
   in (b, world2)
  • What does the type of reaction - namely a -> IO b - mean? By substituting the IO definition, we get a -> RealWorld -> (b, RealWorld). This means that reaction actually has two parameters - the type a actually used inside it, and the value of type RealWorld used for sequencing of I/O actions. That's always the case - any I/O definition has one more parameter compared to what you see in its type signature. This parameter is hidden inside the definition of the IO type:
newtype IO a = Act (RealWorld -> (a, RealWorld))
  • 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 the result of readLn can be send directly to print:
main = readLn >>= print

As you see, the notation:

 do x <- action1
    action2

where action1 has type IO a and action2 has type IO b, translates into:

 action1 >>= (\x -> action2)

where the second argument of (>>=) has the type a -> IO b. It's the way the <- binding is processed - the name on the left-hand side of <- just becomes a parameter of subsequent operations represented as one large I/O action. Note also that if action1 has type IO a then x will just have type a; you can think of the effect of <- as "unpacking" the I/O value of action1 into x. Note also that <- is not a true operator; it's pure syntax, just like do itself. Its meaning results only from the way it gets desugared.

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 the parentheses here; both the (>>) and the (>>=) operators are left-associative, but lambda-bindings always stretches as far to the right as possible, which means that the a and b bindings introduced here are valid for all remaining actions. As an exercise, add the parentheses yourself and translate this definition into the low-level code that explicitly passes "world" values. I think it should be enough to help you finally realize how the do translation and binding operators work.

Oh, no! I forgot the third monadic operator: return. After it is simplified, we can see it does very little! It just combines its two parameters - the value passed and the required "world" value - and immediately returns both of them:

return a world0  =  (a, world0)

How about translating a simple example of return usage? Say,

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

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

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

and you will realize that the print call is executed even for non-negative values of a. If you need to escape from the middle of an I/O definition, you can use an if expression:

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 useful for escaping from the middle of a longish do-expression.

Last exercise: implement a function liftM that lifts operations on plain values to the operations on monadic ones. Its type signature:

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

If that'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, every name in Haskell is bound to one fixed (immutable) value. This greatly simplifies understanding algorithms and code optimization, but it's inappropriate in some cases. As we all know, there are plenty of algorithms that are simpler to implement in terms of updatable variables, arrays and so on. This means that the value associated with a variable, for example, can be different at different execution points, so reading its value can't be considered as a pure function. Imagine, for example, the following code:

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

Does this look strange?

  1. The two calls to readVariable look the same, so the compiler can just reuse the value returned by the first call.
  2. The result of the writeVariable call isn't used so the compiler can (and will!) omit this call completely.
  3. These three calls may be rearranged in any order because they appear to be independent of each other.

This is obviously not what was intended. What's the solution? You already know this - use I/O actions! Doing that guarantees:

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

So, the code above really should be written as:

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

Here, varA has the type IORef Int which means "a variable (reference) in the I/O monad holding a value of type Int". newIORef creates a new variable (reference) and returns it, and then read/write actions use this reference. The value returned by the readIORef varA action depends not only on the variable involved but also on the moment this operation is performed so it can return different values on each call.

Arrays, hash tables and any other _mutable_ data structures are defined in the same way - for each of them, there's an operation that creates new "mutable values" and returns a reference to it. Then value-specific read and write operations in the I/O monad are used. The following code shows an example using mutable arrays:

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, an array of 10 elements with 37 as the initial value at each location is created. After reading the value of the first element (index 1) into a this element's value is changed to 64 and then read again into 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 with I/O actions. For example, a random number generator should return a different value on each call. It looks natural to give it a type involving IO:

rand :: IO Int

Moreover, when you import a C routine you should be careful - if this routine is impure, i.e. its result depends on something "outside the Haskell program" (file system, memory contents, its own static internal state and so on), you should give it an IO type. Otherwise, the compiler can "optimize" repetitive calls to the definition with the same parameters!

For example, we can write a non-IO type for:

foreign import ccall
   sin :: Double -> Double

because the result of sin depends only on its argument, but

foreign import ccall
   tell :: Int -> IO Int

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

Encapsulated mutable data: ST

If you're going to be doing things like sending text to a screen or reading data from a scanner, IO is the type to start with - you can then customise existing I/O operations or add new ones as you see fit. But what if that shiny-new (or classic) algorithm you're working on really only needs mutable state - then having to drag that IO type from main all the way through to wherever you're implementing the algorithm can get quite irritating.

Fortunately there is a better way! One that remains totally pure and yet allows the use of references, arrays, and so on - and it's done using, you guessed it, Haskell's versatile type system (and one extension).

Remember our definition of IO?

newtype IO a = Act (RealWorld -> (a, RealWorld))

Well, the new ST type makes just one change:

newtype ST s a = Act' (s -> (a, s))

If we wanted to, we could use ST to define IO:

type IO a = ST RealWorld a

Let's add some extra definitions:

newSTRef     :: a -> ST s (STRef s a)      -- these are
readSTRef    :: STRef s a -> ST s a        --  usually
writeSTRef   :: STRef s a -> a -> ST s ()  -- primitive

newSTArray   :: Ix i => (i, i) -> ST s (STArray s i e) -- also usually primitive
              

instance Monad (ST s) where
    m >>= k  = let actual' (Act' m) = m in
               Act' $ \s1 -> case actual' m s1 of (x, s2) -> actual' (k x) s2
    return x = Act' $ \s1 -> (x, s1)

...that's right - this new ST type is also monadic!

So what's the big difference between the ST and IO types? In one word - runST:

runST :: (forall s . ST s a) -> a

Yes - it has a very unusual type. But that type allows you to run your stateful computation as if it was a pure definition!

The s type variable in ST is the type of the local state. Moreover, all the fun mutable stuff available for ST is quantified over s:

newSTRef  :: a -> ST s (STRef s a)
newArray_ :: Ix i => (i, i) -> ST s (STArray s i e)

So why does runST have such a funky type? Let's see what would happen if we wrote

makeSTRef :: a -> STRef s a
makeSTRef a = runST (newSTRef a)

This fails, because newSTRef a doesn't work for all state types s - it only works for the s from the return type STRef s a.

This is all sort of wacky, but the result is that you can only run an ST computation where the output type is functionally pure, and makes no references to the internal mutable state of the computation. In exchange for that, there's no access to I/O operations like writing to or reading from the console. The monadic ST type only has references, arrays, and such that are useful for performing pure computations.

Just like RealWorld, the state type doesn't actually mean anything. We never have an actual value of type s, for instance. It's just a way of getting the type system to do the work of ensuring purity is preserved - it's being used like another baton.

On the inside runST uses that newly-made baton to run the computation. When it finishes runST separates the resulting value from the final baton. This value is then returned by runST.

Because the internal implementations of IO and ST are so similar, there's this function:

stToIO :: ST RealWorld a -> IO a

The difference is that ST uses the type system to forbid unsafe behavior like extracting mutable objects from their safe ST wrapping, but allowing purely functional outputs to be performed with all the handy access to mutable references and arrays.

For example, here's a particularly convoluted way to compute the integer that comes after zero:

oneST :: ST s Integer -- note that this works correctly for any s
oneST = do var <- newSTRef 0
           modifySTRef var (+1)
           readSTRef var

one :: Int
one = runST oneST


I/O actions as values

By this point you should understand why it's impossible to use I/O actions inside non-I/O (pure) functions. Such functions just don't get a "baton"; they don't know any "world" value to pass to an I/O action. The RealWorld type is an abstract datatype, so pure functions also can't construct RealWorld values by themselves, and it's a strict type, so undefined also can't be used. So, the prohibition of using I/O actions inside pure functions is maintained by the type system (as it usually is in Haskell).

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

In order to execute the I/O action we need to apply it to some RealWorld value. That can be done only inside other I/O actions, in their "actions chains". And real execution of this action will take place only when this action is called as part of the process of "calculating the final value of world" for main. Look at this partially-simplified example:

main world0 = let skip2chars = getChar >> getChar >> return ()  -- NB: not simplified!
                  (answer, world2) = skip2chars world1
                  ((), world1) = putStr "Press two keys" world0
              in ((), world2)

Here we first write a binding for skip2chars, then another binding involving putStr. But what's the execution order? It's not defined by the order of the let bindings, it's defined by the order of processing "world" values! You can arbitrarily reorder those local bindings - the execution order will be defined by the data dependency with respect to the "world" values that get passed around. Let's see what this main action would have looked like in the do notation:

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

As you can see, we've eliminated two of the let bindings and left only the one defining skip2chars. The non-let actions are executed in the exact order in which they're written, because they pass the "world" value from action to action as we described above. Thus, this version of the function is much easier to understand because we don't have to mentally figure out the data dependency of the "world" value.

Moreover, I/O actions like skip2chars can't be executed directly because they are functions with a RealWorld parameter. To execute them, we need to supply the RealWorld parameter, i.e. insert them in the main chain, placing them in some do sequence executed from main (either directly in the main action, or indirectly in an I/O function called from main). Until that's done, they will remain like any function, in partially evaluated form. And we can work with I/O actions as with any other functions - bind them to names (as we did above), save them in data structures, pass them as function parameters and return them as results - and they won't be performed until you give them that inaugural RealWorld argument!

Example: a list of I/O actions

Let's try defining a list of I/O actions:

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

I used additional parentheses around each action, although they aren't really required. If you still can't believe that these actions won't be executed immediately, just recall the simplifed type of this list:

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, right? Really, any I/O action that you write in a do-expression (or use as a parameter for the (>>)/(>>=) operators) is an expression returning a result of type IO a for some type a. Typically, you use some function that has the type x -> y -> ... -> IO a and provide all the x, y, etc. parameters. But you're not limited to this standard scenario - don't forget that Haskell is a functional language and you're free to compute the functional value required (recall that IO a is really 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 the previous example - that's also OK. Want to see this functional value passed as a parameter? Just look at the definition of when. Hey, we can buy, sell, and rent these I/O actions just like we can with any other functional values! For example, let's define a function that executes all the I/O actions in the list:

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

No mirrors or smoke - we just extract I/O actions from the list and insert them into a chain of I/O operations that should be performed one after another (in the same order that they occurred in the list) to "compute the final world value" of the entire sequence_ call.

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

main = sequence_ ioActions

Haskell's ability to work with I/O actions as with any other (functional and non-functional) values allows us to define control structures of arbitrary complexity. Try, for example, to define a control structure that repeats an action until it returns the False result:

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

Most programming languages don't allow you to define control structures at all, and those that do often require you to use a macro-expansion system. In Haskell, control structures are just trivial functions anyone can write.

Example: returning an I/O action as a result

How about returning an I/O action as the result of a function? Well, we've done this for each I/O definition - they all return I/O actions that need a RealWorld value to be performed. While we usually just execute them as part of a higher-level I/O definition, it's also possible to just collect them without actual execution:

main = do let a = sequence ioActions
              b = when True getChar
              c = getChar >> getChar >> return ()
          putStr "These let-bindings are not executed!"

These assigned I/O actions can be used as parameters to other definitions, or written to global variables, or processed in some other way, or just executed later, as we did in the example with skip2chars.

But how about returning a parameterized I/O action from an I/O definition? Here's a definition that returns the i'th byte from a file represented as a Handle:

readi h i = do hSeek h AbsoluteSeek i
               hGetChar h

So far so good. But how about a definition that returns the i'th byte of a file with a 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 I/O definition that opens a file and returns...an I/O action that will read the specified byte. But we can go further and include the readi body in readfilei:

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

That's a little better. But why do we add h as a parameter to readi if it can be obtained from the environment where readi is now defined? An even shorter version is this:

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

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

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

This way of using I/O actions is very typical for Haskell programs - you just construct one or more I/O actions that you need, with or without parameters, possibly involving the parameters that your "constructor" received, and return them to the caller. Then these I/O actions can be used in the rest of the program without any knowledge about your internal implementation strategy. One thing this can be used for is to partially emulate the OOP (or more precisely, the ADT) programming paradigm.

Example: a memory allocator generator

As an example, one of my programs has a module which is a memory suballocator. It receives the address and size of a large memory block and returns two specialised I/O operations - one to allocate a subblock of a given size and the other to free the allocated subblock:

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 work with references created inside the memoryAllocator definition. Because the creation of these references is a part of the memoryAllocator I/O-action chain, a 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 are read and written in the alloc and free definitions (we'll implement a very simple memory allocator for this example):

      ...
      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 use state available at the moment of their definition. As you can see, it's as easy as in any other functional language, despite Haskell's lack of direct support for impure routines.

The following example uses the operations returned by memoryAllocator, to simultaneously allocate/free blocks in two independent memory buffers:

main = do buf1 <- mallocBytes (2^16)
          buf2 <- mallocBytes (2^20)
          (alloc1, free1) <- memoryAllocator buf1 (2^16)
          (alloc2, free2) <- memoryAllocator buf2 (2^20)
          ptr11 <- alloc1 100
          ptr21 <- alloc2 1000
          free1 ptr11
          free2 ptr21
          ptr12 <- alloc1 100
          ptr22 <- alloc2 1000

Example: emulating OOP with record types

Let's implement the classical OOP example: drawing figures. There are figures of different types: circles, rectangles and so on. The task is to create a heterogeneous list of figures. All figures in this list should support the same set of operations: draw, move and so on. We will define these operations using I/O actions. Instead of a "class" let's define a structure containing implementations of all the operations required:

data Figure = Figure { draw :: IO (),
                       move :: Displacement -> IO ()
                     }

type Displacement = (Int, Int)  -- horizontal and vertical displacement in points

The constructor of each figure's type should just return a Figure record:

circle    :: Point -> Radius -> IO Figure
rectangle :: Point -> Point -> IO Figure

type Point = (Int, Int)  -- point coordinates
type Radius = Int        -- circle radius in points

We will "draw" figures by just printing their current parameters. Let's start with a simplified implementation of the circle and rectangle constructors, without actual move support:

circle center radius = do
    let description = "  Circle at "++show center++" with radius "++show radius
    return $ Figure { draw = putStrLn description }

rectangle from to = do
    let description = "  Rectangle "++show from++"-"++show to)
    return $ Figure { draw = putStrLn description }

As you see, each constructor just returns a fixed draw operation that prints parameters with which the concrete figure was created. Let's test it:

drawAll :: [Figure] -> IO ()
drawAll figures = do putStrLn "Drawing figures:"
                     mapM_ draw figures

main = do figures <- sequence [circle (10,10) 5,
                               circle (20,20) 3,
                               rectangle (10,10) (20,20),
                               rectangle (15,15) (40,40)]
          drawAll figures

Now let's define "full-featured" figures that can actually be moved around. In order to achieve this, we should provide each figure with a mutable variable that holds each figure's current screen location. The type of this variable will be IORef Point. This variable should be created in the figure constructor and manipulated in I/O operations (closures) enclosed in the Figure record:

circle center radius = do
    centerVar <- newIORef center

    let drawF = do center <- readIORef centerVar
                   putStrLn ("  Circle at "++show center
                             ++" with radius "++show radius)

    let moveF (addX,addY) = do (x,y) <- readIORef centerVar
                               writeIORef centerVar (x+addX, y+addY)

    return $ Figure { draw=drawF, move=moveF }

rectangle from to = do
    fromVar <- newIORef from
    toVar   <- newIORef to

    let drawF = do from <- readIORef fromVar
                   to   <- readIORef toVar
                   putStrLn ("  Rectangle "++show from++"-"++show to)

    let moveF (addX,addY) = do (fromX,fromY) <- readIORef fromVar
                               (toX,toY)     <- readIORef toVar
                               writeIORef fromVar (fromX+addX, fromY+addY)
                               writeIORef toVar   (toX+addX, toY+addY)

    return $ Figure { draw=drawF, move=moveF }

Now we can test the code which moves figures around:

main = do figures <- sequence [circle (10,10) 5,
                               rectangle (10,10) (20,20)]
          drawAll figures
          mapM_ (\fig -> move fig (10,10)) figures
          drawAll figures

It's important to realize that we are not limited to including only I/O actions in a record that's intended to simulate a C++/Java-style interface. The record can also include values, IORefs, pure functions - in short, any type of data. For example, we can easily add to the Figure interface fields for area and origin:

data Figure = Figure { draw :: IO (),
                       move :: Displacement -> IO (),
                       area :: Double,
                       origin :: IORef Point
                     }


Exception handling (under development)

Although Haskell provides a set of exception raising/handling features comparable to those in popular OOP languages (C++, Java, C#), this part of the language receives much less attention. This is for two reasons:

  • you just don't need to worry as much about them - most of the time it just works "behind the scenes".
  • Haskell, lacking OOP-style inheritance, doesn't allow the programmer to easily subclass exception types, therefore limiting the flexibility of exception handling.

The Haskell RTS raises more exceptions than traditional languages - pattern match failures, calls with invalid arguments (such as head []) and computations whose results depend on special values undefined and error "...." all raise their own exceptions:

  • example 1:
main = print (f 2)

f 0 = "zero"
f 1 = "one"
  • example 2:
main = print (head [])
  • example 3:
main = print (1 + (error "Value that wasn't initialized or cannot be computed"))

This allows the writing of programs in a much more error-prone way.


Interfacing with C/C++ and foreign libraries (under development)

While Haskell is great at algorithm development, speed isn't its best side. We can combine the best of both languages, though, by writing speed-critical parts of program in C and the rest in Haskell. We just need a way to call C routines from Haskell and vice versa, and to marshal data between the two languages.

We also need to interact with C to use Windows/Linux APIs, linking to various libraries and DLLs. Even interfacing with other languages often requires going through C, which acts as a "common denominator". Chapter 8 of the Haskell 2010 report provides a complete description of interfacing with C.

We will learn to use the FFI via a series of examples. These examples include C/C++ code, so they need C/C++ compilers to be installed, the same will be true if you need to include code written in C/C++ in your program (C/C++ compilers are not required when you just need to link with existing libraries providing APIs with C calling convention). On Unix (and Mac OS?) systems, the system-wide default C/C++ compiler is typically used by GHC installation. On Windows, no default compilers exist, so GHC is typically shipped with a C compiler, and you may find on the download page a GHC distribution bundled with C and C++ compilers. Alternatively, you may find and install a GCC/MinGW version compatible with your GHC installation.

If you need to make your C/C++ code as fast as possible, you may compile your code by Intel compilers instead of GCC. However, these compilers are not free, moreover on Windows, code compiled by Intel compilers may not interact correctly with GHC-compiled code, unless one of them is put into DLLs (due to object file incompatibility).

More links:

C->Haskell
A lightweight tool for implementing access to C libraries from Haskell.
HSFFIG
The Haskell FFI Binding Modules Generator (HSFFIG) is a tool that takes a C library header (".h") and generates Haskell Foreign Function Interface import declarations for items (functions, structures, etc.) the header defines.
MissingPy
MissingPy is really two libraries in one. At its lowest level, MissingPy is a library designed to make it easy to call into Python from Haskell. It provides full support for interpreting arbitrary Python code, interfacing with a good part of the Python/C API, and handling Python objects. It also provides tools for converting between Python objects and their Haskell equivalents. Memory management is handled for you, and Python exceptions get mapped to Haskell Dynamic exceptions. At a higher level, MissingPy contains Haskell interfaces to some Python modules.
HsLua
A Haskell interface to the Lua scripting language

Foreign calls

We begin by learning how to call C routines from Haskell and Haskell definitions from C. The first example consists of three files:

main.hs:

{-# LANGUAGE ForeignFunctionInterface #-}

main = do print "Hello from main"
          c_routine

haskell_definition = print "Hello from haskell_definition"

foreign import ccall safe "prototypes.h"
    c_routine :: IO ()

foreign export ccall
    haskell_definition :: IO ()

vile.c:

#include <stdio.h>
#include "prototypes.h"

void c_routine (void)
{
  printf("Hello from c_routine\n");
  haskell_definition();
}

prototypes.h:

extern void c_routine (void);
extern void haskell_definition (void);

It may be compiled and linked in one step by ghc:

 ghc --make main.hs vile.c

Or, you may compile C module(s) separately and link in ".o" files (this may be preferable if you use make and don't want to recompile unchanged sources; ghc's --make option provides smart recompilation only for ".hs" files):

 ghc -c vile.c
 ghc --make main.hs vile.o

You may use gcc/g++ directly to compile your C/C++ files but I recommend to do linking via ghc because it adds a lot of libraries required for execution of Haskell code. For the same reason, even if main in your program is written in C/C++, I recommend calling it from the Haskell action main - otherwise you'll have to explicitly init/shutdown the GHC RTS (run-time system).

We use the foreign import declaration to import foreign routines into Haskell, and foreign export to export Haskell definitions "outside" for imperative languages to use. Note that import creates a new Haskell symbol (from the external one), while export uses a Haskell symbol previously defined. Technically speaking, both types of declarations create a wrapper that converts the names and calling conventions from C to Haskell or vice versa.

All about the foreign declaration

The ccall specifier in foreign declarations means the use of the C (not C++ !) calling convention. This means that if you want to write the external routine in C++ (instead of C) you should add export "C" specification to its declaration - otherwise you'll get linking errors. Let's rewrite our first example to use C++ instead of C:

prototypes.h:

#ifdef __cplusplus
extern "C" {
#endif

extern void c_routine (void);
extern void haskell_definition (void);

#ifdef __cplusplus
}
#endif

Compile it via:

 ghc --make main.hs vile.cpp

where "vile.cpp" is just a renamed copy of "vile.c" from the first example. Note that the new "prototypes.h" is written to allow compiling it both as C and C++ code. When it's included from "vile.cpp", it's compiled as C++ code. When GHC compiles "main.hs" via the C compiler (enabled by the -fvia-C option), it also includes "prototypes.h" but compiles it in C mode. It's why you need to specify ".h" files in foreign declarations - depending on which Haskell compiler you use, these files may be included to check consistency of C and Haskell declarations.

The quoted part of the foreign declaration may also be used to give the import or export another name - for example,

foreign import ccall safe "prototypes.h CRoutine"
    c_routine :: IO ()

foreign export ccall "HaskellDefinition"
    haskell_definition :: IO ()

specifies that:

  • the C routine called CRoutine will become known as c_routine in Haskell,
  • while the Haskell definition haskell_definition will be known as HaskellDefinition in C.

It's required when the C name doesn't conform to Haskell naming requirements.

Although the Haskell FFI standard tells about many other calling conventions in addition to ccall (e.g. cplusplus, jvm, net) current Haskell implementations support only ccall and stdcall. The latter, also called the "Pascal" calling convention, is used to interface with WinAPI:

foreign import stdcall unsafe "windows.h SetFileApisToOEM"
  setFileApisToOEM :: IO ()

And finally, about the safe/unsafe specifier: a C routine imported with the unsafe keyword is called directly and the Haskell runtime is stopped while the C routine is executed (when there are several OS threads executing the Haskell program, only the current OS thread is delayed). This call doesn't allow recursively entering back into Haskell by calling any Haskell definition - the Haskell RTS is just not prepared for such an event. However, unsafe calls are as quick as calls in C. It's ideal for "momentary" calls that quickly return back to the caller.

When safe is specified, the C routine is called in a safe environment - the Haskell execution context is saved, so it's possible to call back to Haskell and, if the C call takes a long time, another OS thread may be started to execute Haskell code (of course, in threads other than the one that called the C code). This has its own price, though - around 1000 CPU ticks per call.

You can read more about interaction between FFI calls and Haskell concurrency in [7].

Marshalling simple types

Calling by itself is relatively easy; the real problem of interfacing languages with different data models is passing data between them. In this case, there is no guarantee that Haskell's Int is represented in memory the same way as C's int, nor Haskell's Double the same as C's double and so on. While on some platforms they are the same and you can write throw-away programs relying on these, the goal of portability requires you to declare foreign imports and exports using special types described in the FFI standard, which are guaranteed to correspond to C types. These are:

import Foreign.C.Types (               -- equivalent to the following C type:
         CChar, CUChar,                --  char/unsigned char
         CShort, CUShort,              --  short/unsigned short
         CInt, CUInt, CLong, CULong,   --  int/unsigned/long/unsigned long
         CFloat, CDouble...)           --  float/double

Now we can typefully import and export to and from C and Haskell:

foreign import ccall unsafe "math.h"
    c_sin :: CDouble -> CDouble

Note that C routines which behave like pure functions (those whose results depend only on their arguments) are imported without IO in their return type. The const specifier in C is not reflected in Haskell types, so appropriate compiler checks are not performed.

All these numeric types are instances of the same classes as their Haskell cousins (Ord, Num, Show and so on), so you may perform calculations on these data directly. Alternatively, you may convert them to native Haskell types. It's very typical to write simple wrappers around foreign imports and exports just to provide interfaces having native Haskell types:

-- |Type-conversion wrapper around c_sin
sin :: Double -> Double
sin = fromRational . c_sin . toRational

Memory management

Marshalling strings

import Foreign.C.String (   -- representation of strings in C
         CString,           -- = Ptr CChar
         CStringLen)        -- = (Ptr CChar, Int)
foreign import ccall unsafe "string.h"
    c_strlen :: CString -> IO CSize     -- CSize defined in Foreign.C.Types and is equal to size_t
-- |Type-conversion wrapper around c_strlen
strlen :: String -> Int
strlen = ....

Marshalling composite types

A C array may be manipulated in Haskell as StorableArray.

There is no built-in support for marshalling C structures and using C constants in Haskell. These are implemented in the c2hs preprocessor, though.

Binary marshalling (serializing) of data structures of any complexity is implemented in the library module "Binary".

Dynamic calls

DLLs

because i don't have experience of using DLLs, can someone write into this section? Ultimately, we need to consider the following tasks:

  • using DLLs of 3rd-party libraries (such as ziplib)
  • putting your own C code into a DLL to use in Haskell
  • putting Haskell code into a DLL which may be called from C code


The dark side of the I/O monad

Unless you are a systems developer, postgraduate CS student, or have alternate (and eminent!) verifiable qualifications you should have no need whatsoever for this section - here is just one tiny example of what can go wrong if you don't know what you are doing. Look for other solutions!

unsafePerformIO

Do you remember that initial attempt to define getchar?

getchar :: Char

get2chars :: String
get2chars = [a, b] where a = getchar
                         b = getchar

Let's also recall the problems arising from this faux-definition:

  1. Because the Haskell compiler treats all functions as pure (not having side effects), it can avoid "unnecessary" calls to getchar and use one returned value twice;
  2. Even if it does make two calls, there is no way to determine which call should be performed first. Do you want to return the two characters in the order in which they were read, or in the opposite order? Nothing in the definition of get2chars answers this question.

Despite these problems, programmers coming from an imperative language background often look for a way to do this - disguise one or more I/O actions as a pure definition. Having seen procedural entities similar in appearance to:

void putchar(char c);

the thought of just writing:

putchar :: Char -> ()
putchar c = ...

would definitely be more appealing - for example, defining readContents as though it were a pure function:

readContents :: Filename -> String

will certainly simplify the code that uses it. However, those exact same problems are also lurking here:

  1. Attempts to read the contents of files with the same name can be factored (i.e. reduced to a single call) despite the fact that the file (or the current directory) can be changed between calls. Haskell considers all non-IO functions to be pure and feels free to merge multiple calls with the same parameters.
  2. This call is not inserted in a sequence of "world transformations", so the compiler doesn't know at what exact moment you want to execute this action. For example, if the file has one kind of contents at the beginning of the program and another at the end - which contents do you want to see? You have no idea when (or even if) this function is going to get invoked, because Haskell sees this function as pure and feels free to reorder the execution of any or all pure functions as needed.

So, implementing supposedly-pure functions that interact with the Real World is considered to be Bad Behavior. Nice programmers never do it ;-)

Nevertheless, there are (semi-official) ways to use I/O actions inside of pure functions. As you should remember this is prohibited by requiring the RealWorld "baton" in order to call an I/O action. Pure functions don't have the baton, but there is a (ahem) "special" definition that produces this baton from nowhere, uses it to call an I/O action and then throws the resulting "world" away! It's a little low-level mirror-smoke. This particular (and dangerous) definition is:

unsafePerformIO :: IO a -> a

Let's look at how it could be defined:

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

where createNewWorld is an private definition producing a new value of the RealWorld type.

Using unsafePerformIO, you could easily write "pure-looking functions" that actually do I/O inside. But don't do this without a real need, and remember to follow this rule:

  • the compiler doesn't know that you are cheating; it still considers each non-IO function to be a pure one. Therefore, all the usual optimization rules can (and will!) be applied to its execution.

So you must ensure that:

  • The result of each call depends only on its arguments.
  • You don't rely on side-effects of this function, which may be not executed if its results are not needed.

Let's investigate this problem more deeply. Function evaluation in Haskell is determined by a value's necessity - the language computes only the values that are really required to calculate the final result. But what does this mean with respect to the main action? To "calculate the final world's" value, you need to perform all the intermediate I/O actions that are included in the main chain. By using unsafePerformIO we call I/O actions outside of this chain. What guarantee do we have that they will be run at all? None. The only time they will be run is if running them is required to compute the overall function result (which in turn should be required to perform some action in the main chain). This is an example of Haskell's evaluation-by-need strategy. Now you should clearly see the difference:

  • An I/O action inside an I/O definition is guaranteed to execute as long as it is (directly or indirectly) inside the main chain - even when its result isn't used (because the implicit "world" value it returns will be used). You directly specify the order of the action's execution inside the I/O definition. Data dependencies are simulated via the implicit "world" values that are passed from each I/O action to the next.
  • An I/O action inside unsafePerformIO will be performed only if the result of this operation is really used. The evaluation order is not guaranteed and you should not rely on it (except when you're sure about whatever data dependencies may exist).

I should also say that inside the unsafePerformIO call you can organize a small internal chain of I/O actions with the help of the same binding operators and/or do syntactic sugar we've seen above. So here's how we'd rewrite our previous (pure!) definition of one using unsafePerformIO:

one :: Integer
one = unsafePerformIO $ do var <- newIORef 0
                           modifyIORef var (+1)
                           readIORef var

and in this case all the operations in this chain will be performed as long as the result of the unsafePerformIO call is needed. To ensure this, the actual unsafePerformIO implementation evaluates the "world" returned by the action:

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

(The seq operation strictly evaluates its first argument before returning the value of the second one [8]).

inlinePerformIO

inlinePerformIO has the same definition as unsafePerformIO but with the addition of an INLINE pragma:

-- | Just like unsafePerformIO, but we inline it. Big performance gains as
-- it exposes lots of things to further inlining
{-# INLINE inlinePerformIO #-}
inlinePerformIO action = let (a, world1) = action createNewWorld
                         in (world1 `seq` a)

Semantically inlinePerformIO = unsafePerformIO in as much as either of those have any semantics at all.

The difference of course is that inlinePerformIO is even less safe than unsafePerformIO. While ghc will try not to duplicate or common up different uses of unsafePerformIO, we aggressively inline inlinePerformIO. So you can really only use it where the I/O content is really properly pure, like reading from an immutable memory buffer (as in the case of ByteStrings). However things like allocating new buffers should not be done inside inlinePerformIO since that can easily be floated out and performed just once for the whole program, so you end up with many things sharing the same buffer, which would be bad.

So the rule of thumb is that I/O actions wrapped in unsafePerformIO have to be externally pure while with inlinePerformIO it has to be really, really pure or it'll all go horribly wrong.

That said, here's some really hairy code. This should frighten any pure functional programmer...

write :: Int -> (Ptr Word8 -> IO ()) -> Put ()
write !n body = Put $ \c buf@(Buffer fp o u l) ->
  if n <= l
    then write</code> c fp o u l
    else write</code> (flushOld c n fp o u) (newBuffer c n) 0 0 0

  where {-# NOINLINE write</code> #-}
        write</code> c !fp !o !u !l =
          -- warning: this is a tad hardcore
          inlinePerformIO
            (withForeignPtr fp
              (\p -> body $! (p `plusPtr` (o+u))))
          `seq` c () (Buffer fp o (u+n) (l-n))

it's used like:

word8 w = write 1 (\p -> poke p w)

This does not adhere to my rule of thumb above. Don't ask exactly why we claim it's safe :-) (and if anyone really wants to know, ask Ross Paterson who did it first in the Builder monoid)

unsafeInterleaveIO

But there is an even stranger operation:

unsafeInterleaveIO :: IO a -> IO a

Don't let that type signature fool you - unsafeInterleaveIO also uses a dubiously-acquired baton which it uses to set up an underground relay-race for its unsuspecting parameter. If it happens, this seedy race then occurs alongside the offical main relay-race - if they collide, things will get ugly!

So how does unsafeInterleaveIO get that bootlegged baton? Typically by making a forgery of the offical one to keep for itself - it can do this because the I/O action unsafeInterleaveIO returns will be handed the offical baton in the main relay-race. But one miscreant realised there was a simpler way:

{-# NOINLINE unsafeInterleaveIO #-}
unsafeInterleaveIO   :: IO a -> IO a
unsafeInterleaveIO a =  return (unsafePerformIO a)

Why bother with counterfeit copies of batons if you can just make them up?

At least you have some appreciation as to why unsafeInterleaveIO is, well unsafe! Just don't ask - to talk further is bound to cause grief and indignation. I won't say anything more about this ruffian I...use all the time (darn it!)

One can use unsafePerformIO (not unsafeInterleaveIO) to perform I/O operations not in some predefined order but by demand. For example, the following code:

do let c = unsafePerformIO getChar
   do_proc c

will perform the getChar I/O call only when the value of c is really required by the calling code, i.e. it this call will be performed lazily like any regular Haskell computation.

Now imagine the following code:

do let s = [unsafePerformIO getChar, unsafePerformIO getChar, unsafePerformIO getChar]
   do_proc s

The three characters inside this list will be computed on demand too, and this means that their values will depend on the order they are consumed. It is not what we usually want.

unsafeInterleaveIO solves this problem - it performs I/O only on demand but allows you to define the exact internal execution order for parts of your data structure. It is why I wrote that unsafeInterleaveIO makes an illegal copy of the baton:

  • unsafeInterleaveIO accepts an I/O action as a parameter and returns another I/O action as the result:
do str <- unsafeInterleaveIO myGetContents
                    
  • unsafeInterleaveIO doesn't perform any action immediately, it only creates a closure of type a which upon being needed will perform the action specified as the parameter.
  • this action by itself may compute the whole value immediately...or use unsafeInterleaveIO again to defer calculation of some sub-components:
myGetContents = do
   c <- getChar
   s <- unsafeInterleaveIO myGetContents
   return (c:s)

This code will be executed only at the moment when the value of str is really demanded. In this moment, getChar will be performed (with its result assigned to c) and a new lazy-I/O closure will be created - for s. This new closure also contains a link to a myGetContents call.

The resulting list is then returned. It contains the Char that was just read and a link to another myGetContents call as a way to compute the rest of the list. Only at the moment when the next value in the list is required will this operation be performed again.

As a final result, we can postpone the read of the second Char in the list before the first one, but have lazy reading of characters as a whole - bingo!


PS: of course, actual code should include EOF checking; also note that you can read multiple characters/records at each call:

myGetContents = do
   l <- replicateM 512 getChar
   s <- unsafeInterleaveIO myGetContents
   return (l++s)

and we can rewrite myGetContents to avoid needing to use unsafeInterleaveIO where it's called:

myGetContents = unsafeInterleaveIO $ do
   l <- replicateM 512 getChar
   s <- myGetContents
   return (l++s)


Welcome to the machine: the actual GHC implementation

A little disclaimer: I should say that I'm not describing here exactly what a monad is (I don't even completely understand it myself) and my explanation shows only one possible way to implement the I/O monad in Haskell. For example, the hbc compiler and the Hugs interpreter implements the I/O monad via continuations [9]. I also haven't said anything about exception handling, which is a natural part of the "monad" concept. You can read the All About Monads guide to learn more about these topics.

But there is some good news:

  • the I/O monad understanding you've just acquired will work with any implementation and with many other monads. You just can't work with RealWorld values directly.
  • the I/O monad implementation described here is similar to what GHC uses:
newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))

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

Of course, other compilers e.g. yhc/nhc (jhc, too?) define IO in other ways.

The Yhc/nhc98 implementation

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

This implementation makes the World disappear somewhat[10], and returns Either a result of type 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 won't overoptimise it.


Further reading

[1] This tutorial is largely based on Simon Peyton Jones's paper Tackling the awkward squad: monadic input/output, concurrency, exceptions, and foreign-language calls in Haskell. I hope that my tutorial improves his original explanation of the Haskell I/O system and brings it closer to the point of view of new Haskell programmers. But if you need to learn about concurrency, exceptions and the FFI in Haskell/GHC, the original paper is the best source of information.

[2] You can find more information about concurrency, the FFI and STM at the GHC/Concurrency#Starting points page.

[3] The Arrays page contains exhaustive explanations about using mutable arrays.

[4] Look also at the Using monads page, which contains tutorials and papers really describing these mysterious monads.

[5] An explanation of the basic monad functions, with examples, can be found in the reference guide A tour of the Haskell Monad functions, by Henk-Jan van Tuyl.

[6] Official FFI specifications can be found on the page The Haskell 98 Foreign Function Interface 1.0: An Addendum to the Haskell 98 Report

[7] Using the FFI in multithreaded programs is described in Extending the Haskell Foreign Function Interface with Concurrency

[8] This particular behaviour is not a requirement of Haskell 2010, so the operation of seq may differ between various Haskell implementations - if you're not sure, staying within the I/O monad is the safest option.

[9] How to Declare an Imperative by Phil Wadler provides an explanation of how this can be done.

[10] The RealWorld type can even be replaced e.g. Functional I/O Using System Tokens by Lennart Augustsson.

Do you have more questions? Ask in the haskell-cafe mailing list.

To-do list

If you are interested in adding more information to this manual, please add your questions/topics here.

Topics:

  • fixIO and mdo
  • Q monad

Questions:

  • split (>>=)/(>>)/return section and do section, more examples of using binding operators
  • IORef detailed explanation (==const*), usage examples, syntax sugar, unboxed refs
  • explanation of how the actual data "in" mutable references are inside RealWorld, rather than inside the references themselves (IORef, IOArray & co.)
  • control structures developing - much more examples
  • unsafePerformIO usage examples: global variable, ByteString, other examples
  • how unsafeInterLeaveIO can be seen as a kind of concurrency, and therefore isn't so unsafe (unlike unsafeInterleaveST which really is unsafe)
  • discussion about different senses of safe/unsafe (like breaking equational reasoning vs. invoking undefined behaviour (so can corrupt the run-time system))
  • actual GHC implementation - how to write low-level definitions based on example of newIORef's implementation

This manual is collective work, so feel free to add more information to it yourself. The final goal is to collectively develop a comprehensive manual for using the I/O monad.