<<

Imp erative

Simon L Peyton Jones

Dept of Computing Science University of Glasgow

Email simonpjwadlerdcsglagsowacuk

Octob er

This paper appears in

ACM Symposium on Principles Of Programming Languages POPL Charleston Jan

pp This copy corrects a few minor typographical errors in the published version

Abstract IO are constructed by gluing together smaller pro

grams that do so Section Combined with higher

We present a new mo del based on monads for p erform

order functions and this gives a

ing inputoutput in a nonstrict purely functional lan

highly expressive medium in which to express IO

guage It is comp osable extensible ecient requires no

p erforming computations Section quite the

extensions to the and extends smo othly to

reverse of the sentiment with which we b egan this

incorp orate mixedlanguage working and inplace array

section

up dates

We compare the monadic approach to IO with other

standard approaches dialogues and continuations

Section and eect systems and linear types Sec

Introduction

tion

Inputoutput has always app eared to b e one of the less

 It is easily extensible The key to our implementation

satisfactory features of purely functional languages

is to extend Haskell with a single form that allows one

ting action into the functional paradigm feels like tting

to call an any pro cedure written in the programming

a square blo ck into a round hole Closely related dicul

language Kernighan Ritchie without

ties are asso ciated with p erforming inplace up date op er

losing Section Using

ations on arrays and calling arbitrary pro cedures written

it programmers can readily extend the p ower of the

in some other p ossibly sideeecting language

IO system by writing Haskell functions which call

op erating system pro cedures

Some mostlyfunctional languages such as Lisp or SML

deal successfully with inputoutput by using side eects

 It is ecient Our Haskell has C as its

We fo cus on purelyfunctional solutions which rule out

target co de Given a Haskell program p erforming an

side eects for two reasons Firstly the absence of side

IO lo op the compiler can pro duce C co de which is

eects p ermits unrestricted use of equational reasoning

very similar to that which one would write by hand

and program transformation Secondly we are interested

Section

in nonstrict languages in which the order of evaluation

 Its eciency is achieved by applying simple pro

and hence the order of any side eects is delib erately

gram transformations We use unboxed data types

unsp ecied laziness and side eect are fundamentally in

Peyton Jones Launchbury to exp ose rep

imical

resentation and orderofevaluation detail to co de

There is no shortage of prop osals for inputoutput in lazy

improving transformations rather than relying on ad

functional languages some of which we survey later but

hoc optimisations in the co de generator Section

no one solution has b ecome accepted as the consensus

 It extends uniformly to provide interleaved IO and

This pap er outlines a new approach based on monads

reference types Section

Moggi Wadler Wadler with a num

b er of noteworthy features

 It extends uniformly to support incremental arrays

with inplace update Section Our implementa

 It is composable Large programs which engage in tion is ecient enough that we can dene monolithic

Haskell array op erations in terms of incremental ar mainIO IO

rays Hudak have prop osed a similar metho based mainIO putcIO

on continuations Our metho d is more general than

This is the p oint at which b eing is converted to doing

his in the following sense monads can implement

when executed the putcIO action will b e p erformed and

continuations but not the converse

write an exclamation mark to the standard output

 It is based only on the Hind leyMilner type system

Some other prop osals require linear types or existen

Comp osing IO op erations

tial types ours do es not

The functions dened ab ove allow one to dene a single

We have implemented all that we describ e in the con

action but how can actions b e combined For example

text of a compiler for Haskell Hudak et al with

how can we write a program to print two exclamation

the exception of the extension to arrays and reference

marks To do so we introduce two glue combinators

types The entire IO system provided by our compiler

doneIO IO

is written in Haskell using the nonstandard extensions

seqIO IO a IO b IO b

we describ e b elow The languages standard Dialogue

interface for IO is supp orted by providing a to

The comp ound action m seqIO n is p erformed by rst

convert a Dialogue into our IO monad The system is

p erforming m and then p erforming n returning whatever

freely available by FTP

n returns as the result of the comp ound action Back

We do not claim any fundamental expressiveness or e quotes are Haskells syntax for an inx op erator The

ciency which is not obtainable through existing systems action doneIO do es no IO and returns the unit value

except where arrays are concerned Nevertheless we feel

To illustrate here is an action putsIO which puts a

that the entire system works particularly smo othly as a

string to the standard output

whole from the standp oint of b oth programmer and im

putsIO Char IO

plementor

putsIO doneIO

putsIO aas putcIO a seqIO

Overview

putsIO as

We need a way to reconcile being with doing an expres

We can now use putsIO to dene a program which prints

sion in a functional language denotes a value while an

hello twice

IO should perform an action We integrate

mainIO hello seqIO hello

these worlds by providing a type IO a denoting actions

where

that when performed may do some IO and then return

hello putsIO hello

a value of type a The following provide simple Unix

avoured IO op erations

This example illustrates the distinction b etween an action

and its p erformance hello is an action which happ ens to

getcIO IO Char

b e p erformed twice The program is precisely equivalent

putcIO Char IO

to one in which putsIO hello is substituted for either

Here getcIO is an action which when p erformed reads a

or b oth of the o ccurrences of hello In short programs

character from the standard input and returns that char

remain referentially transparent

acter and putcIO a is an action which when p erformed

In general an action may also return a value Again

writes the character a to the standard output Actions

there are two combinators The rst is again trivial

which have nothing interesting to return such as putcIO

return the empty tuple whose type is also written

unitIO a IO a

Notice the distinction b etween an action and its p erfor

If x is of type a then unitIO x denotes the action that

mance Think of an action as a script which is p er

when p erformed do es nothing save return x The second

formed by executing it Actions themselves are rstclass

combines two actions

citizens How then are actions p erformed In our sys

tem the value of the entire program is a single p erhaps

bindIO IO a a IO b IO b

large action called mainIO and the program is executed

by p erforming this action For example the following is If m IO a and k a IO b then m bindIO k

a legal Haskell program denotes the action that when p erformed b ehaves as fol

lows rst p erform action m yielding a value x of type easier by dening new actionmanipulating combinators

a then p erform action k x yielding a value y of type b For example the denition of putsIO given ab ove uses

and then return value y To illustrate here is an action explicit recursion Here is an alternative way to write

that echoes the standard input to the standard output putsIO which do es not do so

In Haskell x e stands for a lambda abstraction the

putsIO as seqsIO map putcIO as

b o dy of the abstraction extends as far as p ossible

The map applies putcIO to each character in the list as to

echo IO

pro duce a list of actions The combinator seqsIO takes

echo getcIO bindIO a

a list of actions and p erforms them in sequence that is

if a eof then

it encapsulates the recursion It is easy to dene seqsIO

doneIO

thus

else

putcIO a seqIO

seqsIO IO a IO

echo

seqsIO doneIO

seqsIO aas a seqIO seqsIO as

The combinators bindIO and unitIO are generalisations

of seqIO and doneIO Here are denitions for the latter

or even using the standard listpro cessing function

in terms of the former

foldr thus

doneIO unitIO

seqsIO foldr seqIO doneIO

m seqIO n m bindIO a n

To take another example here is a function which writes

The combinators have a useful algebra doneIO and

a given number of spaces to the standard output

seqIO form a monoid while bindIO and unitIO form

a monad Moggi Wadler Wadler

spaceIO Int IO

spaceIO n

seqsIO take n repeat putcIO

Imp erative programming

The functions take and repeat are standard list

It will not have escap ed the readers notice that programs

pro cessing functions with nothing to do with IO from

written in the monadic style lo ok rather similar to imp er

Haskells standard prelude The function repeat takes a

ative programs For example the echo program in C

value and returns an innite list each of whose elements

might lo ok something like this

is the given value The function take takes a prex of

given length from a list

echo

loop a getchara

These necessarily examples could easily b e pro

if a eof

grammed with explicit recursion without signicant loss

return

of clarity or even a gain The p oint we are making is

else putchara

that it is easy for the programmer to dene new glue to

goto loop

combine actions in just the way which is suitable for the

program b eing written Its a bit like b eing able to dene

your own control structures in an imp erative language

Indeed as we discuss later our compiler translates the

echo function into essentially this C co de Do es the

monadic style force one in eect to write a functional

Calling C directly

facsimile of an imp erative program thereby losing any

Since the primitive functions putcIO getcIO and so

advantages of writing in a functional language We b e

on must ultimately b e implemented by a call to the un

lieve not

derlying op erating system it is natural to provide the

Firstly the style in which one writes the functional pro

ability to call any op erating system function directly To

grams internal computation is unaected For instance

achieve this we provide a new form of expression the

the argument to putsIO can b e computed using the usual

ccall whose general form is

listpro cessing op erations provided by a functional lan

ccall proc e ::: e

n

guage list comprehensions map app end and the like

Secondly the p ower of higherorder functions and non Here proc is the name of a C pro cedure and e ::: e

n

strict semantics can b e used to IO programming are the parameters to b e passed to it This expression

is an action with type IO Int when p erformed it calls Request and Response are algebraic data types which

the named pro cedure and delivers its result as the value embo dy all the p ossible IO op erations and their results

of the action Here for example are the denitions of resp ectively

getcIO and putcIO

data Request Putc Char Getc

putcIO a ccall putchar a data Response OK OKCh Char

getcIO ccall getchar

For the purp oses of exp osition we have grossly simpli

These ccalls directly invoke the systemprovided func ed these data types compared with those in standard

tions no further runtime supp ort is necessary Using this Haskell A system wrapp er program rep eatedly gets

single primitive allows us to implement our entire IO the next request from the list of requests returned by

system in Haskell main interprets and p erforms it and attaches the re

sp onse to the end of the resp onse list to which main is

We dene ccall to b e a language construct rather than

applied

simply a function b ecause

Here for example is the echo program written using a

Dialogue In Haskell xsn extracts the nth element

 The rst argument must b e the literal name of the

from the list xs

C pro cedures to b e called and not say an expres

sion which evaluates to a string which is the name of

echo Dialogue

the function Type information alone cannot express

echo resps Getc

this

if a eof

then

 Dierent C pro cedures take dierent numbers of ar

else Putc a

guments and some take a variable number of ar

echo drop resps

guments It would b e p ossible to check the type

where

correctness of the C call by reading the signature of

OKCh a resps

the C pro cedure but we do not at present do so

The diculties with this programming style are all to o

 Dierent C pro cedures take arguments of dierent

obvious and have b een well rehearsed elsewhere Perry

types and sizes At present we only p ermit the

arguments to b e of base types such as Char Int

Float Double and so on though we are working on

 It is easy to extract the wrong element of the re

extensions which allow structured arguments to b e

sp onses a synchronisation error This may show up

built

in a variety of ways If the in the ab ove program

was erroneously written as the program would

Treating ccall as a construct allows these variations to

fail with a patternmathing error in getCharIO if it

b e accomo dated without diculty

were written it would deadlo ck

 The Response has to contain a constructor

for every p ossible resp onse to every request Even

Comparison with other IO styles

though Putc may only ever return a resp onse OKChar

In this section we briey compare our approach with two

the patternmatching p erformed by get has to take

other p opular ones dialogues and continuations

account of all these other resp onses

 Even more seriously the style is not comp osable

Dialogues

there is no direct way to take two values of type

Dialogue and combine them to make a larger value

The IO system sp ecied for the Haskell language Hudak

of type Dialogue try it

et al is based on dialogues also called lazy streams

Dwelly ODonnell Thompson In

Dialogues and the IO monad have equal expressive p ower

Haskell the value of the program has type Dialogue a

as Figure demonstrates by using Dialogues to emu

synonym for a function b etween a list of IO resp onses to

late the IO monad and vice versa The function dToIO

a list of IO requests

which emulates Dialogues in terms of IO is rather cu

type Dialogue Response Request rious b ecause it involves applying the single dialogue

main Dialogue d to b oth b ottom ? and later to the real list

getcC Char Result Result

Dialogue to IO

doneC Result

dToIO Dialogue IO

dToIO d

Using these primitives the echo program can b e written

case d bottom of

as follows

doneIO

echo Result Result

qqs doReq q bindIO

echo c getcC a

dToIO rs tail d rrs

if a eof then

then c

bottom a

else putcC a echo c

bottom error Should never be evaluated

Since we might want to do some more IO after the echo

doReq Request IO Response

ing is completed we must provide echo with a continua

doReq GetChar f

tion c to express what to do when echo is nished This

getCharIO f bindIO c

extra argument is required for every IOp erforming

unitIO OKChar c

function if it is to b e comp osable a p ervasive and tire

doReq PutChar f c

some feature

putCharIO f c seqIO unitIO OK

The ab ove presentation of continuationstyle IO is a lit

tle dierent from those cited ab ove In all those descrip

IO to Dialogue

tions Result is an algebraic data type with a construc

type IO a Response

tor for each primitive IO op eration As with Dialogues

a Request Response

execution is driven by a wrapp er program which eval

uates main p erforms the op eration indicated by the con

ioToD IO Dialogue

structor and applies the continuation inside the construc

ioToD action rs case action rs of

tor to the result This approach has the disadvantage

qs qs

that it requires existential types if p olymorphic op era

tions such as those we introduce later in Section are

unitIO v rs v rs

to b e supp orted

bindIO op fop

rs let v qs rs op rs

An obvious improvement which we have not seen previ

v qs rs fop v rs

ously suggested is to implement the primitive continu

in v qsqs rs

ation op erations such as putcC getcC and doneC di

rectly making the Result type an

Figure Converting b etween Dialogue and IO

with no op erations dened on it other than the primi

tives themselves This solves the problem

Continuations are easily emulated by the IO monad and

of resp onses Hudak Sundaresh Peyton Jones

vice versa as Figure shows The comparison b etween

This causes b oth duplicated work and a space

the monadic and continuation approach is further ex

leak but no more ecient purelyfunctional emulation is

plored in Section

known The reverse function ioToD do es not suer from

these problems and this asymmetry is the main reason

that Dialogues are sp ecied as primitive in Haskell We

Implementing monadic IO

return to this this matter in Section

So far we have shown that an entire IO system can b e

expressed in terms of ccall bindIO and unitIO and of

Continuations

course the IO type itself How are these combinators to

The continuationstyle IO mo del Gordon Hudak

b e implemented One p ossibility is to build them in as

Sundaresh Karlsson Perry pro

primitives but it turns out to b e b oth simpler and more

vides primitive IO op erations which take as one of their

ecient to implement all except ccall in Haskell

arguments a continuation which says what to do after the

The idea is that an action of type IO a is implemented as

IO op eration is p erformed

a function which takes as its input a value representing

main Result the entire current of the world and returns a pair

putcC Char Result Result consisting of a value representing the new state of the

unitIO a w MkIORes a w

Continuations to IO

bindIO m k w case m w of

type Result IO

MkIORes a w k a w

cToIO Result IO

Notice that bindIO and unitIO carefully avoid duplicat

cToIO r r

ing the world Provided that the primitive ccall ac

tions are combined only with these combinators we can

putCharC File Char Result Result

guarantee that the ccalls wil l be linked in a single lin

putCharC f c k putCharIO f c seqIO k

ear chain connected by data dep endencies in which each

ccall consumes the world state pro duced by the previous

getCharC File Char

one In turn this means that the ccall op erations can

Char Result Result

up date the real world in place

getCharC f k getCharIO f thenIO k

Implementing ccall

IO to continuations

type IO a a Result Result

So much for the combinators All that remains is the

implementation of ccall The only complication here is

ioToC IO Result

that we must arrange to evaluate the arguments to the

ioToC action action nopC

ccall b efore passing them to C

This is very similar to the argument evaluation required

unitIO v k k v

for builtin functions such as addition for which we have

bindIO op fop k op a fop a k

earlier developed the idea of unboxed data types Pey

ton Jones Launchbury These allow representa

putCharIO f c k putCharC f c k

tion and orderofevaluation information to b e exp osed to

getCharIO f k getCharC f c k c

co deimproving transformations For example consider

the expression xx where x is of type Int The improve

Figure Converting b etween continuations and IO

ment we want to express is that x need only b e evaluated

once

world and the result of type a

The key idea is to dene the type Int which is usually

primitive as a structured algebraic data type with a sin

type IO a World IORes a

gle constructor MkInt like this

data IORes a MkIORes a World

data Int MkInt Int

The type declaration introduces a type synomym for IO

and the auxiliary algebraic datatype IORes simply pairs

A value of type Int is represented by a p ointer to a heap

the result with the new world Recall that the value of

allo cated ob ject which may either b e an unevaluated sus

the entire program is of type IO The type World is

p ension or a MkInt constructor containing the machine

abstract with only one op eration dened on it namely

bitpattern for the integer This bitpattern is of type

ccall Conceptually the program is executed by apply

Int

ing main to a value of type World representing current

Now that Int is given structure we can make explicit

state of the world extracting the resulting World value

the evaluation p erformed by by giving the following

from the MkIORes constructor and applying any changes

denition which expresses in terms of the primitive

embo died therein to the real world

machine op eration

If implemented literally such a system would b e unwork

ably exp ensive The key to making it cheap is to ensure a b case a of

that the world state is used in a singlethreaded way so MkInt a

that IO operations can be applied immediately to the real case b of

world One way to ensure this would b e to do a global MkInt b

analysis of the program A much simpler way is to make MkInt a b

IO into an abstract data type which encapsulates the data

Inlining this denition of in the expression xx and

types IO and IORes and the combinators bindIO and

p erforming simple routine simplications gives the fol

unitIO Here are suitable denitions for the latter

lowing in which x is evaluated only once

case x of to b e instantiated at an unboxed type such as Int

MkInt x MkInt x x

Thirdly the ccall primitive is recognised by the co de

generator and expanded to an actual call to C Sp eci

Unboxed types and ccall are not part of standard

cally the expression

Haskell They are mainly used internally in our compiler

though we do also make them available to programmers

case ccall proc a b c w of

as a nonstandard extension

MkIORes n w

We apply exactly the same ideas to ccall In particular

generates the C statement

instead of implementing ccall directly we unfold every

use of ccall to make the argument evaluation explicit

n procabc

b efore using the truly primitive op eration ccall For

example the uses of ccall in the denitions of putcIO

and getcIO given ab ove Section are unfolded thus

This simple translation is al l that the code generator is

required to do The rest is done by generic program trans

putcIO a w

formations that is transformations which are not sp ecic

case a of

to IO or even to unboxing Peyton Jones Launchbury

MkChar a

case ccall putchar a w of

MkIORes n w MkIORes w

Where has the world gone

getcIO w

case ccall getchar w of

But what has b ecome of the world values in the nal

MkIORes n w

C co de The world value manipulated by the program

MkIORes MkChar n w

represents the current state of the real world but since the

real world is up dated in place the world value carries no

Like Int the type Char is implemented as an algebraic

useful information Hence we simply arrange that no co de

data type thus

is ever generated to move values of type World This is

easy to do as type information is preserved throughout

data Char MkChar Int

the compiler In particular the world is never loaded

The outer case expression of putcIO therefore evalu

into a register stored in a data structure or passed to C

ates a and extracts the bitpattern a which is passed

pro cedure calls

to ccall The inner case expression evaluates the ex

Is it p ossible then to disp ense with the world in the func

pression ccall putchar a w which returns a pair

tional part of the implementation as well For example

constructed by MkIORes consisting of the value n re

can we dene the IORes type and bindIO combinators

turned by the C pro cedure putchar which is ignored

like this

and a new world w which is returned

data IORes a MkIORes a

In the case of getcIO the primitive unboxed value n

bindIO m k w case m w of

returned by getchar is not ignored as it is in putcIO

MkIORes a k a w

rather it is wrapp ed in a MkChar constructor and re

turned as part of the result

No we cannot To see this supp ose that bindIO was ap

plied to a function k which discarded its argument Then

The dierences b etween ccall and ccall are as follows

if bindIO was unfolded and the expression k r w was

Firstly ccall takes only unboxed arguments ready to

simplied there would be no remaining data dependency

call C directly

to force the call of k to occur after that of m A compiler

Secondly it returns a pair built with MkIORes contain

would b e free to call them in either order which destroys

ing an unboxed integer result direct from the C call The

the IO sequencing

IORes type is very similar to IORes

To reiterate the world is there to form a linear chain

data IORes MkIORes Int World

of data dep endencies b etween successive ccalls It is

quite safe to exp ose the representation of the IO type

IORes and IORes are distinct types b ecause while our

to co deimproving transformations b ecause the chain of

extended type system recognises unboxed types it do es

data dep endencies will prevent any transformations which

not p ermit p olymorphic type constructors such as IORes

reorder the ccalls Once the co de generator is reached

though the work of the world values is done so it is safe A continuationpassing implementation

to generate no co de for them

Like most abstract data types there is more than one way

to implement IO In particular it is p ossible to implement

the IO abstract type using a continuationpassing style

The type IO a is represented by a function which takes

echo revisited

a continuation exp ecting a value of type a and returns a

value of the opaque type Result

The implementation we have outlined is certainly simple

but is it ecient Perhaps surprisingly the answer is an

type IO a a Result Result

emphatic yes The reason for this is that b ecause the

combinators are written in Haskell the compiler can un

It is easy to implement bindIO and unitIO

fold them at al l their call sites that is p erform pro cedure

inlining

bindIO m k cont m a k a cont

unitIO r cont cont r

Very little sp ecialpurp ose co de is required in the compiler

to achieve this eect essentially all that is required is

What is there to choose b etween these this representation

that the Haskell denitions of bindIO unitIO putcIO

of the IO type and the one we describ ed initially Sec

and so on b e unfolded by the compiler In contrast if

tion The ma jor tradeo seems to b e this with the

bindIO were primitive then every call to bindIO will re

continuationpassing representation every use of bindIO

quire the construction of two heapallo cated closures for

even if unfolded requires the construction of one heap

its two arguments Even if bindIO itself to ok no time at

allo cated continuation In contrast the implementation

all this would b e a heavy cost

we describ ed earlier keeps the continuation implicitly on

the stack which is slightly cheaper in our system

To illustrate the eectiveness of the approach we have

outlined we return to the echo program of Section If

There is a cost to pay for the earlier representation

we take the co de there unfold the calls of seqIO doneIO

namely that a heavily leftskewed comp osition of bindIOs

eof putcIO and getcIO and do some simplication we

can cause the stack to grow rather large In contrast

get the following

the continuationpassing implementation may use a lot of

heap for such a comp osition but its stack usage is con

echo w

stant

case ccall getchar w of

MkIORes a w

The main p oint is that the implementor is free to choose

case a eof of

the representation for IO based only on considerations of

T MkIORes w

eciency and resource usage the choice makes no dier

F case ccall putchar a w of

ence to the interface seen by the programmer

MkIORes n w echo w

When this is compiled using the simple co degenerator

Extensions to the IO monad

describ ed the following C is pro duced

echo

Delayed IO

int a

So far all IO op erations have b een strictly sequenced

a getchar

along a single trunk Sometimes though such strict

if a eof

sequencing is unwanted For example almost all lazy

retVal unitTuple

functionallanguage IO systems provide a readFile

RETURN

primitive which returns the entire contents of a sp eci

else

ed le as a list of characters It is often vital that this

putchara

primitive should have lazy semantics that is the le is

JUMP echo

op ened but only actually read when the resulting list is

evaluated The relative ordering of other IO op erations

JUMP and RETURN are artefacts of our use of C as a target and the reading of the le is immaterial provided the

machine co de Peyton Jones They expand only le is not simultaneously written This lazy read is usu

to a machine instruction or two This is very close to ally implemented by some ad hoc magic in the runtime

the C one would write by hand We know of no other system but within the monadic framework it is easy to

implementation of IO with b etter eciency generalise the idea

What is required is a new combinator for the IO monad Asynchronous IO

delayIO which forks o a new branch from the main

An even more dangerous but still useful combinator is

trunk

performIO whose type is as follows

delayIO IO a IO a

performIO IO a a

When p erformed delayIO action immediately re

It allows p otentially sideeecting op erations to take place

turns a susp ension which when it is subsequently forced

which are not attached to the main trunk at all The

will p erform the IO sp ecied by action The relative

pro of obligation here is that any such side eects do not

interleaving of the IO op erations on the trunk and the

aect the b ehaviour of the rest of the program An obvi

branch is therefore dep endent on the evaluation order

ous application is when one wishes to call a C pro cedure

of the program

which really is a pro cedures from a numer

The delayIO combinator is dangerous alb eit useful b e

ical analysis are one example

cause the correctness of the program now requires that

Implementation The implementation is quite simple

arbitrary interleaving of IO op erations on the trunk

and branch cannot aect the result This condition

performIO m case m newWorld of

cannot be guaranteed by the compiler it is a proof obli

MkIORes r w r

gation for the programmer In practice we exp ect that

delayIO will b e used mainly by system programmers

Here newWorld is a value of type World conjured up out

of thin air and discarded when the action m has b een

With the aid of delayIO and a few new primitives such

p erformed

as fOpenIO it is easy to write a lazy readFile

readFile Char IO Char

Assignment and reference variables

readFile s fOpenIO s bindIO f

Earlier in Section we discussed the apparently in

delayIO lazyRd f

soluble ineciency of dToIO the function which emu

lates Dialogues using the IO monad We can solve this

lazyRd File IO Char

problem by providing an extra generalpurp ose mecha

lazyRd f

nism that of assignable reference types and op erations

readChar f bindIO a

over them Ireland

if a eof then

fCloseIO f seqIO

newVar a IO Ref a

unitIO

assignVar Ref a a IO

else

deRefVar Ref a IO a

delayIO lazyRd f bindIO as

unitIO aas

The call newVar x allo cates a fresh variable containing

the value x the call assignVar v x assigns value x to

The delayIO combinator provides essentially the p ower

variable v and the call deRefVar v fetches the value in

of Gordons suspend op erator Gordon

variable v By making these sideeecting op erations part

Implementation A nice feature of the implementation

of the IO monad we make sure that their order of evalu

technique outlined in Section is that delayIO is very

ation and hence semantics is readily explicable

easy to dene

With the aid of these primitives it is p ossible to write

an ecent emulation of Dialogues using IO Figure

delayIO m w let res case m w of

The idea is to mimic a system which directly implements

MkIORes r w r

Dialogues which follows the pro cessing of each request

in

with a destructive up date to add a new resp onse to the

MkIORes res w

end of the list of resp onses Notice the uses of delayIO

In contrast to bindIO notice how delayIO duplicates the

which reects the fact that there is no guarantee that

world w and then discards the nal world w of the de

dialogue will not evaluate a resp onse b efore it has emit

layed branch it is this which allows the unsynchronised

ted a request If this o ccurs the unassigned variable is

interleaving of IO op erations on the branch with those

evaluated which elicits a suitable error message

on the trunk

References in languages such as ML require a weakened

form of p olymorphism in order to maintain type safety

The b ehaviour of these op erations is sp ecied by the usual

dToIO Dialogue IO

laws

dToIO dialogue

newVar error Synch bindIO rsV

lookup i new v v

delayIO deRefVar rsV bindIO rs

lookup i update i v x v

run dialogue rs rsV

lookup i update j v x lookup i x

run Request Ref Response IO

where i 6 j in the last equation In practice these op er

run v doneIO

ations would b e more complex one needs a way to sp ecify

run reqreqs v

the array b ounds for instance But the ab ove suces to

doReq req bindIO r

explicate the main p oints

newVar error Synch bindIO rsV

delayIO deRefVar rsV bindIO rs

The ecient way to implement the up date op eration is

assignVar v rrs seqIO

to overwrite the sp ecied entry of the array but in a pure

run reqs rsV

functional language this is only safe if there are no other

p ointers to the array extant when the up date op eration

Figure Ecient conversion from Dialogue to IO

is p erformed An array satisfying this prop erty is called

single threaded following Schmidt Schmidt

As an example consider the following problem An oc

Tofte For instance in ML a fresh reference to

currence is either a denition pairing an index with a

an empty list has type a list ref where the type

value or a use of an index

variable a is weak and so may b e instantiated only

once In contrast here a fresh reference to an empty list

data Occ Def Ind Val Use Ind

has type IO Ref a and the type variable a is normal

But no lack of safety arises b ecause an expression of this

For illustration take Ind Int and Val Char Given

type allo cates a new reference each time it is evaluated

a list os of o ccurrences the call uses os returns for each

The only way to change a value of type IO Ref a to one

use the most recently dened value or if there is no

of type Ref a is via bindIO but now the variable of type

previous denition If

Ref a is not letb ound and so can only b e instantiated

os Def a Def b Use

once anyway Hence the extra complication of weak type

Def c Use Use

variables required in languages with side eects seems

unnecessary here Were indebted to Martin Odersky for

then

this observation

uses os a b c

Arrays Here is the co de

uses Occ Val

The approach we take to IO smo othly extends to ar

uses os loop os new

rays with inplace up date Hudak has recently prop osed

a similar metho d based on continuations For IO the

loop Occ Arr Val

monad and continuation approaches are interdenable

loop x

For arrays it turns out that monads can implement con

loop Def i v os x loop os update i v x

tinuations but not the converse

loop Use i os x lookup i x loop os x

Let Arr b e the type of arrays taking indexes of type Ind

and yielding values of type Val There are three op era

The up date in this program can b e p erformed by over

tions on this type

writing but some care is required with the order of eval

uation In the last line the lo okup must o ccur before the

new Val Arr

recursive call which may up date the array Some work has

lookup Ind Arr Val

b een done on analysing when up date can b e p erformed in

update Ind Val Arr Arr

place but it is rather tricky Bloss Hudak

The call new v returns an array with all entries set to v

the call lookup i x returns the value at index i in ar

ray x and the call update i v x returns an array where

index i has value v and the remainder is identical to x

Monadic arrays unitA vvs

We b elieve that single threading is to o imp ortant to leave

This is somewhat lengthier than the previous example

to the vagaries of an analyser Instead we use monads to

but it is guaranteed safe to implement up date by over

guarantee single threading in much the same way as was

writing

done with IO Analogous to the type IO a the monad of

IO actions we provide an abstract type A a the monad

of array transformers

Continuation arrays

newA Val A a a

An alternative metho d of guaranteeing single threading

lookupA Ind A Val

for arrays has b een prop osed by Hudak Like the

updateA Ind Val A

previous work of Swarup Reddy Ireland it is

unitA a A a

based on continuations but unlike that work it requires

bindA A a a A b A b

no change to the type system

As with the array monad one denes an abstract type

For purp oses of sp ecication we can dene these in terms

supp orting various op erations The type is C z and the

of the pro ceeding op erations as follows

op erations are as follows

type A a Arr a Arr

newC Val C z z

lookupC Ind Val C z C z

newA v m fst m new v

updateC Ind Val C z C z

lookupA i x lookup i x x

unitC z C z

updateA i v x update i v x

unitA a x ax

Here a continuation of type C z represents the remaining

m bindA k x let ay m x in k a y

series of actions to b e p erformed on the array eventually

returning via unitC a value of type z

A little thought shows that these op erations are indeed

single threaded The only op eration that could duplicate

For purp oses of sp ecication we can dene these in terms

the array is lookupA but this may b e implemented as

of the array op erations as follows

follows rst fetch the entry at the given index in the

array and then return the pair consisting of this value

type C z Arr z

and the p ointer to the array To enforce the necessary

sequencing we augment the ab ove sp ecication with the

newC v c c new v

requirement that lookupA and updateA are strict in the

lookupC i d x d lookup i x x

index and array arguments but need not b e strict in the

updateC i v c x c update i v x

value

unitC z x z

The ab ove is given for purp oses of sp ecication only the

Again these op erations are single threaded if lookupC

actual implementation is along the lines of Section

and updateC are strict in the index and array arguments

For convenience dene seqA in terms of bindA in the

For convenience dene

usual way

m c m c

m seqA n m bindA a n

This lets us omit some parentheses since m x n

Here is the denitionuse problem reco ded in monadic

b ecomes m x n

style

Here is the denitionuse problem reco ded in continua

uses Occ Val

tion style

uses os newA loopA os

uses Occ Val

loopA Occ A Val uses os newC loopC os unitC

loopA unitA

loopA Def i v os updateA i v seqA loopC Occ Val C z C z

loopA os loopC c c

loopA Use i os lookupA i bindA v loopC Def i v os c updateC i v

loopA os bindA vs loopC os c

loopC Use i os c lookupC i v type B a z a C z C z

loopC os vs

c vvs newB v m newC v m unitC

lookupB i d lookupC i d

This is remarkably similar to the monadic style where

updateB i v d updateC i v d

takes the place of bindA and seqA and the current

unitB a d d a

continuation c takes the place of unitA If c plays the

m bindB k d m a k a d

role of unitA why do we need unitC Because it acts as

the top level continuation Again it is easy to prove this implementation satises the

given sp ecications

However there are two things to note ab out the contin

uation style First the types are rather more complex So monads are more p owerful than continuations but

compare the types of loopA and loopC Second the only b ecause of the types It is not clear whether this

monadic style abstracts away from the notion of contin is simply an artifact of the HindleyMilner type system

uation so there are no o ccurrences of c cluttering the or whether the types are revealing a dierence of funda

dention of loopA mental imp ortance Our own intuition is the latter but

its only an intuition

Monads vs continuations

Conclusion

We can formally compare the p ower of the two approaches

The IO approach outlined earlier manipulates a global

by attempting to implement each in terms of the other

state namely the entire state of the machine accessible

Despite their similarities the two approaches are not

via a C program What has b een shown in this section

equivalent Monads are p owerful enough to implement

is that this approach extends smo othly to manipulating

continuations but not quite vice versa

local state such as a single array Further although the

monad and continuation approaches are interconvertible

To implement continuations in terms of monads is sim

for IO they are not for arrays monads are p owerful

plicity itself

enough to dene continuations but not the reverse

type C z A z

For actual use with Haskell we require a slightly more so

phisticated set of op erations The type A must take extra

newC v c newA v c

parameters corresp onding to the index and value types

lookupC i d lookupA i bindA d

the op eration newA should take the array b ounds and so

updateC i v c updateA i v seqA c

on By using a variant of newA that creates an unini

unitC unitA

tialised array and returns the array after all up dates are

nished it is p ossible to implement Haskell primitives

It is an easy exercise in equational reasoning to to prove

for creating arrays in terms of the simpler monad op era

that this implementation is correct in terms of the sp eci

tions Thus the same strategy that works for implement

cations in Sections and

ing IO should work for implementing arrays use a small

The reverse implementation is not p ossible The trouble

set of primitives based on monads and dep end on pro

is the annoying extra type variable z app earing in the

gram transformation to make this adequately ecient

types of lookupC and updateC This forces the introduc

One question that remains is how well this approach ex

tion of a spurious type variable into any attempt to dene

tends to situations where one wishes to manipulate more

monads in terms of continuations Instead of a type A a

than one state at a time as when combining IO with

the b est one can do is to dene a type B a z Here are

array op erations or op erating on two arrays In this re

the types of the new op erations

sp ect eect systems or linear types may b e sup erior see

newB Val B a a a

b elow

lookupB Ind B Val z

updateB Ind Val B z

unitB a B a z

Related work

bindB B a z a B b z B b z

Eect systems

And here are the implementations in terms of continua

Giord and Lucassen introduced eect systems which

tions

use types to record the sideeects p erformed by a pro

gram and to determine which comp onents of a program For example here is the echo program again written in

can run in parallel without interference Giord Lu the style suggested by the Clean IO system

cassen The original notion of eect was fairly

echo File File World World

crude there b eing only four p ossible eects pure no ef

echo fi fo w if a eof

fect allo cate may allo cate storage function may read

then w

storage pro cedure may write storage New systems are

else echo putChar fo a w

more rened allowing eects to b e expressed separately

where

for dierent regions of store Jouvelot Giord

wa getChar fi w

A theoretical precursor of the eects work is that of

Compared to the monad approach this suers from a

Reynolds which also used types to record where eects

number of drawbacks programs b ecome more cluttered

could o ccur and where parallelism was allowed Reynolds

the linear type system has to b e explained to the pro

Reynolds

grammer and implemented in the compiler and co de

Our work is similar to the ab ove in its commitment to

improving transformations need to b e reexamined to en

use types to indicate eects But eect systems are de

sure they preserve linearity The latter problem may b e

signed for impure strict functional languaes where the

imp ortant Wakeling found that some standard transfor

order of sequencing is implicit Our work is designed for

mations could not b e p erformed in the presence of linear

pure lazy functional languages and the purp ose of the

ity Wakeling

bind op eration is to make sequencing explicit where it

The big advantage of a linear type system is that it en

is required

ables us to write programs which manipulate more than

With eect systems one may use the usual laws of

one piece of up datable state at a time The monadic and

equational reasoning on any program segment without

continuationpassing presentations of arrays given ab ove

a write side eect Our work diers in that the laws

pass the array around implicitly and hence can only eas

of equational reasoning apply even where side eects are

ily handle one at a time This is an imp ortant area for

al lowed This is essential b ecause the optimisation phase

future work

of our compiler is based on equational reasoning

On the practical side the Clean work is impressive They

On the other hand eect systems make it very easy

have written a library of highlevel routines to call the

to combine programs with dierent eects In our ap

Macintosh window system and demonstrated that it is

proach each dierent eect would corresp ond to a dier

p ossible to build pure functional programs with sophisti

ent monad type one for IO one for each array manip

cated user interfaces The same approach should work for

ulated and so on and it is not so clear how one go es

monads and another area for future work is to conrm

ab out combining eects

that this is the case

Linear types

Conclusions and further work

The implementation of the IO monad given in Section

We have b een pleasantly surprised by b oth the expres

is safe b ecause and only b ecause the co de that manipu

siveness and the eciency of the approach we have de

lates the world never duplicates or destroys it We guar

scrib ed For example we have found that while it is p os

antee safety by making the IO type abstract so that user

sible to write comp osable IO programs in other styles

has no direct access to the world

it is almost imp ossible not to do so in using the monadic

approach

An alternative is to allow the user access to the world

but introduce a type system that guarantees that the

Plenty remains to b e done We are working on our im

world can never b e duplicated or destroyed A number of

plementation of arrays this in turn feeds into the ability

type systems have b een prop osed along such lines Some

to pass structured values in ccalls we have not yet im

have b een based on Girards linear logic Girard

plemented assignable reference types

and this remains an area of active exploration Abram

sky Guzman Hudak Wadler An More imp ortantly the mo del we have desrib ed concerns

other is the type system prop osed by the Nijmegen Clean only the IO infrastructure Much more work needs to b e

group which is more adho c but has b een tested in prac done to design libraries of functions built on top of this

tical applications similar to our own Achten Groningen infrastructure which present a higherlevel interface to

Plasmeijer the programmer Achten Groningen Plasmeijer

Hammond Wadler Brady P Hudak July Continuationbased mutable ab

stract datatypes or how to have your state and

munge it to o YALEUDCSRR Depart

Acknowledgements

ment of Science

This work to ok place in the context of the team building

P Hudak SL Peyton Jones PL Wadler Arvind B Boutel

the Glasgow Haskell compiler Cordy Hall Kevin Ham

J Fairbairn J Fasel M Guzman K Hammond J

mond and Will Partain David Watt Jo e Morris John

Hughes T Johnsson R Kieburtz RS Nikhil W

Launchbury also made very helpful suggestions ab out our

Partain J Peterson May Rep ort on the

presentation We gratefully acknowledge their help

functional Haskell Ver

sion SIGPLAN Notices

References

P Hudak RS Sundaresh March On the ex

pressiveness of purelyfunctional IO systems

YALEUDCSRR Department of Com

S Abramsky Computational interpretations of

puter Science Yale University

linear logic DOC Dept of Computing

Imp erial College

Paul Hudak Aug A semantic mo del of reference

counting and its abstraction Pro c ACM Con

PM Achten JHG van Groningen MJ Plasmeijer

ference on Lisp and Functional Programming

Highlevel sp ecication of IO in func

tional languages in Pro c Glasgow Workshop on

E Ireland March Writing interactive and le

Functional Programming Launchbury et al ed

pro cessing functional programs MSc

Springer Verlag

Victoria University of Wellington

A Bloss Sept Up date analysis and the ecient im

P Jouvelot D Giord Jan Algebraic reconstruc

plementation of functional aggregates in Func

tion of types and eects in th ACM Symp o

tional Programming Languages and Computer

sium on Principles of Programming Languages

Architecture London ACM

POPL Orlando ACM

A Dwelly Sept Dialogue combinators and dy

Kent Karlsson Nebula a functional op erating

namic user interfaces in Functional Program

system Chalmers Inst Goteb org

ming Languages and Computer Architecture

BW Kernighan DM Ritchie The C programming

London ACM

language Prentice Hall

DK Giord JM Lucassen Aug Integrating func

E Moggi June Computational

tional and imp erative programming in ACM

and monads in Logic in Cal

Conference on Lisp and Functional Program

ifornia IEEE

ming MIT ACM

JT ODonnell Dialogues a basis for construct

JY Girard Linear Logic Theoretical Computer

ing programming environments in Pro c ACM

Science

Symp osium on Language Issues in Programming

A Gordon Feb PFL a kernel scheme for func

Environments Seattle ACM

tional IO TR Computer Lab University

N Perry The implementation of practical func

of Cambridge

tional programming languages PhD thesis Im

JC Guzman P Hudak Singlethreaded p oly

p erial College London

morphic lambda calculus in Pro c th Annual

SL Peyton Jones Apr Implementing lazy func

IEEE Symp osium on Logic in Computer Science

tional languages on sto ck hardware the Spine

K Hammond PL Wadler D Brady Imp erate b e

less Tagless Gmachine Journal of Functional

imp erative Department of Computer Science

Programming

Univ of Glasgow

SL Peyton Jones Oct Converting streams to con

tinuations and vice versa Electronic mail on

Haskell mailing list

SL Peyton Jones J Launchbury Sept Unboxed

values as rst class citizens in Functional Pro

gramming Languages and Computer Architec

ture Boston Hughes ed LNCS Springer

Verlag

J Reynolds The essence of Algol in Algorithmic

Languages de Bakker van Vliet eds North

Holland

J Reynolds Syntactic control of interference part

I I in International Collo quium on Automata

Languages and Programming

DA Schmidt Apr Detecting global variables in de

notational sp ecications TOPLAS

V Swarup US Reddy E Ireland Sept Assign

ments for applicative languages in Functional

Programming Languages and Computer Archi

tecture Boston Hughes ed LNCS Springer

Verlag

SJ Thompson Interactive functional programs a

metho d and a formal semantics in Declarative

Programming DA Turner ed Addison Wesley

M Tofte Nov Type inference for p olymorphic ref

erences Information and Computation

PL Wadler Linear types can change the world

in Programming concepts and metho ds M Broy

C Jones eds North Holland

PL Wadler Jan The essence of functional pro

gramming in Pro c Principles of Programming

Languages ACM

PL Wadler June Comprehending monads in

Pro c ACM Conference on Lisp and Functional

Programming Nice ACM

D Wakeling Nov Linearity and laziness PhD

thesis Department of Computer Science Univer

sity of York