Comprehending Monads

Philip Wadler

University of Glasgow

Abstract

Category theorists invented monads in the s to concisely express certain

asp ects of universal Functional programmers invented list comprehensions

in the s to concisely express certain programs involving lists This pap er shows

how list comprehensions may b e generalised to an arbitrary and howthe

resulting programming feature can concisely express in a pure functional language

some programs that manipulate state handle exceptions parse text or invokecon

tinuations A new solution to the old problem of destructive array up date is also

presented No knowledge of theory is assumed

Intro duction

Is there a waytocombine the indulgences of impurity with the blessings of purity

Impure strict functional languages such as Standard ML Mil HMT and Scheme

RC supp ort a wide variety of features such as assigning to state handling exceptions

and invoking continuations Pure lazy functional languages suchasHaskell HPW or

Miranda Tur eschew such features b ecause they are incompatible with the advan

tages of lazy evaluation and equational reasoning advantages that have b een describ ed

at length elsewhere Hug BW

Purity has its regrets and all programmers in pure functional languages will recall

some moment when an impure feature has tempted them For instance if a counter is

required to generate unique names then an assignable variable seems just the ticket In

such cases it is always p ossible to mimic the required impure feature by straightforward

or instance a counter can b e simulated by mo difying the relevant though tedious means F

functions to accept an additional parameter the counters currentvalue and return an

additional result the counters up dated value

Miranda is a trademark of ResearchSoftware Limited

Authors address Department of Computing Science University of Glasgow G QQ Scotland Elec

tronic mail wadlercsglasgowacuk

This pap er app eared in Mathematical Structures in Computer Science volume pp copy

right Cambridge University Press This version corrects a few small errors in the published version An

earlier version app eared in ACM ConferenceonLispandFunctional Programming Nice June

This pap er describ es a new metho for structuring pure programs that mimic impure

features This metho d do es not completely eliminate the tension b etween purity and

impurity but it do es relax it a little bit It increases the readability of the resulting

programs and it eliminates the p ossibility of certain silly errors that might otherwise

arise such as accidentally passing the wrong value for the counter parameter

The inspiration for this technique comes from the work of Eugenio Moggi Moga

Mogb His goal was to provide a way of structuring the semantic description of features

such as state exceptions and continuations His discovery was that the notion of a monad

from suits this purp ose By dening an interpretation of calculus in

an arbitrary monad he provided a framework that could describ e all these features and

more

It is relatively straightforward to adopt Moggis technique of structuring denotational

sp ecications into a technique for structuring functional programs This pap er presents a

simplied version of Moggis ideas framed in a way b etter suited to functional program

mers than semanticists in particular no knowledge of category theory is assumed

The pap er contains two signicant new contributions

The rst contribution is a new language feature the monad comprehension This

generalises the familiar notion of list comprehension Wad due originally to Burstall

and Darlington and found in KRCTur Miranda Haskell and other languages Monad

comprehensions are not essential to the structuring technique describ ed here but they do

provide a pleasant syntax for expressing programs structured in this way

The second contribution is a new solution to the old problem of destructive array

een up date The solution consists of two abstract data typ es with ten op erations b etw

them Under this approach the usual typing discipline eg HindleyMilner extended

with abstract data typ es is sucient to guarantee that arrayupdatemay safely b e

implemented byoverwriting Tomyknowledge this solution has never b een prop osed

b efore and its discovery comes as a surprise considering the plethora of more elab orate

solutions that have b een prop osed these include syntactic restrictions Sch runtime

checks Hol abstract interpretation Huda Hudb Blo and exotic typ e systems

GH Wad Wad That monads led to the discovery of this solution must countas

a p oint in their favour

Why has this solution not b een discovered b efore One likely reason is that the data

typ es involve higherorder functions in an essential way The usual axiomatisation of

arrays involves only rstorder functions index update andnewarray as describ ed in

Section and so apparentlyitdidnotoccurtoanyone to search for an abstract data

typ e based on higherorder functions Incidentally the higherorder nature of the solution

means that it cannot b e applied in rstorder languages such as or OBJ It also

casts doubt on Goguens that rstorder languages are sucient for most purp oses

Gog

Monads and monad comprehensions help to clarify and unify some previous prop osals

for incorp orating various features into functional languages exceptions Wad Spi

parsers Wad Fai FL and nondeterminism HO In particular Spiveys work

Spi is notable for p ointing out indep endently of Moggi that monads provide a frame

work for exception handling

There is a translation scheme from calculus into an arbitrary monad Indeed there

are twoschemes one yielding callbyvalue semantics and one yielding callbyname

These can b e used to systematically transform languages with state exceptions continu

ations or other features into a pure functional language Two applications are given One

is to derive callbyvalue and callbyname interpretations for a simple nondeterministic

language this ts the work of Hughes and ODonnell HO into the more general frame

work given here The other is to apply the callbyvalue scheme in the monad of continu

ations the result is the familiar continuationpassing style transformation It remains an

op en question whether there is a translation scheme that corresp onds to callbyneed as

opp osed to callbyname

Akey feature of the monad approach is the use of typ es to indicate what parts of

a program mayhave what sorts of eects In this it is similar in spirit to Giord and

Lucassens eect systems GL

The examples in this pap er are based on Haskell HPW though any lazy functional

language incorp orating the HindleyMilner typ e system would work as well

The remainder of this pap er is organised as follows Section uses list comprehensions

to motivate the concept of a monad and intro duces monad comprehensions Section

shows that variable binding as in let terms and control of evaluation order can b e

mo delled bytwo trivial monads Section explores the use of monads to structure pro

grams that manipulate state and presents the new solution to the array up date problem

Two examples are considered renaming b ound variables and interpreting a simple im

p erative language Section extends monad comprehensions to include lters Section

intro duces the concept of monad morphism and gives a simple pro of of the equivalence of

two programs Section catalogues three more monads parsers exceptions and continu

ations Section giv es the translation schemes for interpreting calculus in an arbitrary

monad Two examples are considered giving a semantics to a nondeterministic language

and deriving continuationpassing style

Comprehensions and monads

Lists

Let us write Mx for the data typ e of lists with elements of typ e x In Haskell this is

usually written x For example   MInt and a b cM Char We write

map for the higherorder function that applies a function to eachelment of a list

map x y Mx My

In Haskell typ e variables are written with small letters eg x and y and typ e construc

tors are written with capital letters eg M For example if code Char Int maps a

character to its ASCI I co de then map code a b c   Observethat

i map id id 

ii map g f map g map f 

Here id is the identity function id x x and g f is function comp osition g f x

g fx

In category theory the notions of type and function are generalised to object and

An op erator M taking each ob ject x into an ob ject Mx combined with an

op erator map taking eacharrow f x y into an arrow map f Mx My and

satisfying i andii is called a Categorists prefer to use the same symb ol for

b oth op erators and so would write Mf where we write map f

The function unit converts a value into a lists and the function join con

catenates a list of lists into a list

unit x Mx

Mx Mx join M

For example unit and join     Observe that

iii map f unit unit f 

iv map f join join map map f 

Laws iii and iv may b e derived by a systematic transformation of the p olymorphic

typ es of unit and join The idea of deriving laws from typ es go es by the slogan theorems

for free Wad and is a consequence of Reynolds abstraction theorem for p olymorphic

lamb da calculus Rey

In categorical terms unit and join are natural transformations Rather than treat unit

as a single function with a p olymorphic typ e categorists treat it as a family of arrows

unit unit f for anyobjects unit x Mx one for each ob ject x satisfying map f

x y x

x and y and any arrow f x y between them They treat join similarly Natural

transformation is a simpler concept than p olymorphic function but we will stickwith

p olymorphism since its a more familiar concept to functional programmers

Comprehensions

Many functional languages provide a form of list comprehension analogous to compre

hension For example

x  y j x   y         

In general a comprehension has the form t j q where t is a term and q is a qualier We

use the letters t u v to range over terms and p q r to range over qualiers A qualier

is either empty or a generator x u where x is a variable and u is a listvalued

term or a comp osition of qualiers p  q Comprehensions are dened by the following

rules

t j unit t 

t j x u map x t u 

t j p  q join t jq j p 

In Haskell terms are written x t rather than the more common x  t Note

the reversal of qualiers in rule nesting q inside p on the righthand side means that

as we exp ect variables b ound in p may b e used in q but not viceversa

For those familiar with list comprehensions the empty qualier and the parentheses

in qualier comp ositions will app ear strange This is b ecause they are not needed We

will shortly prove that qualier comp osition is asso ciative and has the empty qualier

as unit Thus we need not write parentheses in qualier comp ositions since p  q  r

and p  q  r are equivalent and we need not write q  or q b ecause b oth are

equivalent to the simpler q The only remaining use of is to write t j whichwe

abbreviate t

Most languages that include list comprehensions also allow another form of qualier

known as a lter the treatmentofwhich is p ostp oned until Section

As a simple example wehave

sqr x j x  

fby g

map x sqr x  

freducing map g

  

The comprehension in the initial example is computed as

x  y j x   y 

fby g

join x  y j y  j x 

g fby

join map y x  y  j x 

fby g

join map x map y x  y  

freducing map g

join map x x   x  

freducing map g

join       

freducing join g

       

From i iv and wemay derive further laws

ftj q map f t j q 

x j x u u 

u u

t j p  x u jq  r t j p  q  r 

x x

In function f must contain no free o ccurrences of variables b ound by qualier q and

u

stands for term t with term u substituted for each free o ccurrence of in the term t

x

u

Law isproved by induction over the variable x and similarly for the qualier r

x

structure of qualiers the pro of uses laws ii iv and Law isanimmediate

consequence of laws i and Law isagainproved by induction over the structure

of qualiers and the pro of uses laws

As promised wenowshow that qualier comp osition is asso ciative and has the empty

qualier as a unit

I t j  q t j q 

II t j q  t j q 

r  III t j p  q  r t j p  q 

First observe that I III are equivalent resp ectively to the following

I join unit id 

II join map unit id 

III join join join map join 

To see that II andII are equivalent start with the left side of II and simplify

t j q 

fby g

join t j j q

fby g

join unit t j q

fby g

map unit t j q  join

That II implies II is immediate For the converse taket j q tobex j x u and

apply The other two equivalences are seen similarly

Second observe that laws I III do indeed hold For example

join unit  join   

join map unit  join   

join join   join     

join map join   join     

Use induction over lists to proveI andII and over list of lists to proveIII

Monads

The comprehension notation suits data structures other than lists Sets and bags are

obvious examples and we shall encounter many others Insp ection of the foregoing lets

us isolate the conditions under which a comprehension notation is sensible

For our purp oses a monad is an op erator M on typ es together with a triple of functions

map x y Mx My

unit x Mx

join M Mx Mx

satisfying laws i iv and I III

Every monad gives rise to a notion of comprehension via laws The three

laws establish a corresp ondence b etween the three comp onents of a monad and the three

forms of qualier asso ciates unit with the empty qualier asso ciates map with

generators and asso ciates join with qualier comp osition The resulting notion of

comprehension is guaranteed to b e sensible in that it necessarily satises laws

and I III

In what follows we will need to distinguish many monads WewriteM alone to stand

M M M M

for the monad leaving the triple map  unit  join implicit and we write t j q

to indicate in which monad a comprehension is to b e interpreted The monad of lists as

describ ed ab ove will b e written List

Set

As an example take Set to b e the set typ e constructor map to b e the of a

Set

set under a function unit to b e the function that takes an elementinto a singleton set

Set

join to b e the union of a set of sets and

Set

map f x f fx j x x g

Set

unit x f x g

S

Set

x x  join

The resulting comprehension notation is the familiar one for sets For instance x  y j

Set

x  y y sp ecies the cartesian pro duct of sets x and y x

We can recover unit map and join from the comprehension notation

unit x x

map f x fx j x x

x x j x x  x x  join

Here we adopt the convention that if x has typ e x then x has typ e Mx and x has typ e

M Mx

Thus not only can we derive comprehensions from monads but we can also derive

monads from comprehensions Dene a comprehension structure to b e anyinterpretation

of the syntax of comprehensions that satises laws andI III Anymonad

gives rise to a comprehension structure via laws as wehave seen these imply

and I III Converselyany comprehension structure gives rise to a monad

structure via laws it is easy to verify that these imply i iv and

and hence I III

The concept we arrived at by generalising list comprehensions mathematicians arrived

at by a rather dierent route It rst arose in homological algebra in the s with

the undistinguished name standard construction sort of a mathematical equivalentof

hey you The next name triple was not much of an impro vement Finally it was

baptised a monad Nowadays it can b e found in any standard text on category theory

Mac BW LS

The concept we call a monad is slightly stronger than what a categorist means by that

name we are using what a categorist would call a strong monad in a cartesian closed

category Rougly sp eaking a category is cartesian closed if it has enough structure to

interpret calculus In particular asso ciated with anypairofobjectstyp es x and y

there is an ob ject x y representing the space of all arrows functions from x to y

Recall that M is a functor if for anyarrow f x y there is an arrow map f Mx

My satisfying i andii This functor is strong if it is itself represented by a single

arrow map x y Mx My This is all second nature to a generous functional

programmer but a stingy categorist provides such structure only when it is needed

It is needed here as evidenced by Moggis requirement that a computational monad

havea strength a function t x  My M x  y satisfying certain laws Moga In

a cartesian closed category a monad with a strength is equivalent to a monad with a

 y strong functor as describ ed ab ove In our framework the strength is dened by t x

y Following Haskell we write x  y for pairs and also x  y for the x  y j y

corresp onding pro duct typ e

Monads were conceived in the s list comprehensions in the s They have

quite indep endent origins but t with each other remarkably well As often happ ens a

common truth may underlie apparently disparate phenomena and it maytake a decade

or more b efore this underlying commonality is unearthed

Two trivial monads

The identity monad

The identity monad is the trivial monad sp ecied by

typ e Id x x

Id

map fx fx

Id

unit x x

Id

join x x 

Id Id id

so map unit and bind are all just the identity function A comprehension in the

identity monad is like a let term

Id

t j x u

x t u

x u in t  let

Similarly a sequence of qualiers corresp onds to a sequence of nested let terms

Id

t j x u  y v letx u in let y v in t 

Since y is b ound after x it app ears in the inner let term In the following comprehen

sions in the identity monad will b e written in preference to let terms as the twoare

equivalent

In the HindleyMilner typ e system terms and let terms dier in that the latter

mayintro duce p olymorphism The key factor allowing let terms to play this role is that

the syntax pairs eachboundvariable with its binding term Since monad comprehensions

have a similar prop erty it seems reasonable that they to o could b e used to intro duce

p olymorphism However the following do es not require comprehensions that intro duce

p olymorphism so weleave exploration of this issue for the future

The strictness monad

Sometimes it is necessary to control order of evaluation in a lazy functional program This

is usually achieved with the computable function strict dened by

strict f x if x then fx else 

Op erationally strict f x is reduced by rst reducing x to weak head normal form WHNF

and then reducing the application fx Alternatively it is safe to reduce x and fx in

parallel but not allow access to the result until x is in WHNF

We can use this function as the basis of a monad

typ e Str x x

Str

map fx strict f x

Str

unit x x

Str

join x x 

Str

This is the same as the identity monad except for the denition of map Monad laws

i iii iv and I III are satised but lawii b ecomes an inequality

Str Str Str

map g map f v map g f 

So Str is not quite a monad categorists mightcallita lax monad Comprehensions for

lax monads are dened bylaws just as for monads Law remains valid but

laws and b ecome inequalities

We will use Str comprehensions to control the evaluation order of lazy programs For

instance the op erational interpretation of

Str

t j x u  y v

is as follows reduce u to WHNF bind x to the value of u reduce v to WHNF bind y

to value of v then reduce t Alternatively it is safe to reduce t u and v in parallel but

and v are in WHNF not to allow access to the result until b oth u

Manipulating state

Pro cedural programming languages op erate by assigning to a state this is also p ossible in

impure functional languages such as Standard ML In pure functional languages assign

mentmay b e simulated by passing around a value representing the current state This

section shows how the monad of state transformers and the corresp onding comprehension

can b e used to structure programs written in this style

State transformers

Fixatyp e S of states The monad of state transformers ST is dened by

typ e ST x S x  S

ST Id

map f x s fx s j x  s xs

ST

unit x s x  s

ST Id

join x s x  s j x  s xs x  s xs 

Recall the equivalence of Id comprehensions and let terms as explained in Section

A state transformer of typ e x takes a state and returns a value of typ e x and a new state

The unit takes the value x into the state transformer s x  s that returns x and

leaves the state unchanged Wehave that

ST Id

x  y j x x  y y s x  y  s j x  s xs y  s ys 

This applies the state transformer x to the state s yielding the value x and the new state

y to the state s yielding the value y and the s it then applies a second transformer

newer state s nally it returns a value consisting of x paired with y and the nal state

s

Two useful op erations in this monad are

fetch ST S

fetch s s  s

assign S ST

assign s s  s 

The rst of these fetches the currentvalue of the state leaving the state unchanged the

second discards the old state assigning the new state to b e the given value Here is

the typ e that contains only the value

A third useful op eration is

init S ST x x

Id

init s x x j x  s xs 

This applies the state transformer x to a given initial state s it returns the value computed

by the state transformer while discarding the nal state

Example Renaming

Saywe wish to rename all b ound variables in a lamb da term A suitable data typ e Term

for representing lamb da terms is dened in Figure in Standard ML and Figure in

Haskell New names are to b e generated by counting we assume there is a function

mkname Int Name

that given an integer computes a name We also assume a function

subst Name Name Term Term

such that subst x xt substitutes x for each free o ccurrence of x in t

A solution to this problem in the impure functional language Standard ML is shown

in Figure The impure feature we are concerned with here is state the solution uses

a reference N to an assignable lo cation containing an integer The functions and their

typ es are

newname Name 

renamer Term Term 

rename Term Term 

Note that newname and renamer are not true functions as they dep end on the state

In particular newname returns a dierent name each time it is called and so requires

the dummy parameter to give it the form of a function However rename is a

true function since it always generates new names starting from Understanding the

program requires a knowledge of which functions aect the state and whichdonot

This is not always easy to see renamer is not a true function even though it do es not

y direct reference to the state N b ecause it do es contain an indirect reference contain an

through newname but rename is a true function even though it references renamer

An equivalent solution in a pure functional language is shown in Figure This

explicitly passes around an integer that is used to generate new names The functions

and their typ es are

newname Int Name  Int 

renamer Term Int Term  Int 

rename Term Term 

The function newname generates a new name from the integer and returns an incremented

integer the function renamer takes a term and an integer and returns a renamed term

with names generated from the given integer paired with the nal integer generated

The function rename takes a term and returns a renamed term with names generated

from This program is straightforward but can b e dicult to read b ecause it contains

a great deal of plumbing to pass around the state It is relatively easy to intro duce

errors into such programs by writing n where n is intended or the like This plumbing

y problem can b e more severe in a program of greater complexit

Finally a solution of this problem using the monad of state transformers is shown in

Figure The state is taken as S Int The functions and their typ es are now

newname ST Name 

renamer Term ST Name 

rename Term Term 

The monadic program is simply a dierentway of writing the pure program expanding the

monad comprehensions in Figure and simplifying would yield the program in Figure

Typ es in the monadic program can b e seen to corresp ond directly to the typ es in the

impure program an impure function of typ e U V that aects the state corresp onds

to a pure function of typ e U ST V Thus renamer has typ e Term Term in the

impure program and typ e Term ST Term in the monadic program and newname

has typ e Name in the impure program and typ e ST Name which is isomorphic to

ST Name in the pure program Unlike the impure program typ es in the monadic

program make manifest where the state is aected and so do the ST comprehensions

The plumbing is now handled implicitly by the state transformer rather than explic

itlyVarious kinds of errors that are p ossible in the pure program such as accidentally

writing n in place of n are imp ossible in the monadic program Further the typ e sys

tem ensures that plumbing is handled in an appropriate wayFor example one might

b e tempted to write say App renamer t renamer u fortherighthand side of the last

equation dening renamer but this would b e detected as a typ e error

into an abstract data typ e on which Safety can b e further ensured by making ST

ST ST ST

map unit join fetch assign and init are the only op erations This guarantees

that one cannot mix the state transformer abstraction with other functions which handle

the state inappropriately This idea will b e pursued in the next section

Impure functional languages such as Standard ML are restricted to using a strict

or callbyvalue order of evaluation b ecause otherwise the eect of the assignments

b ecomes very dicult to predict Programs using the monad of state transformers can b e

written in languages using either a strict callbyvalue or lazy callbyname order of

evaluation The statetransformer comprehensions make clear exactly the order in which

the assignments take eect regardless of the order of evaluation used

Reasoning ab out programs in impure functional languages is problematic although

not imp ossible see MT for one approach In contrast programs written using

monads like all pure programs can b e reasoned ab out in the usual way substituting

equals for equals They also satisfy additional laws such as the following laws on qualiers

ST

x fetch  y fetch x fetch  y x 

ST

assign u  y fetch assign u  y u 

assign u  assign v assign v 

and on terms

ST

init u t t 

ST ST

init u t j assign v  q init v t j q 

ST ST

init u t j q  assign v init u t j q 

These together with the comprehension laws and I III allow one to

use equational reasoning to prove prop erties of programs that manipulate state

Arrayupdate

Let Arr b e the typ e of arrays taking indexes of typ e Ix and yielding values of typ e Val

The key op erations on this typ e are

newarray Val Arr 

index Ix Arr Val 

update Ix Val Arr Arr 

Here newarray v returns an arraywithallentries set to v and index i a returns the value

at index i in array a and update i v a returns an array where index i has value v and the

remainder is identical to a In equations

index i newarray v v 

index i update i v a v 

index i update i va index i a  if i i

The ecientway to implement the up date op eration is to overwrite the sp ecied entry of

the array but in a pure functional language this is only safe if there are no other p ointers

to the arrayextant when the up date op eration is p erformed

Now consider the monad of state transformers taking the state typ e S Arr so that

typ e ST x Arr x  Arr 

Variants of the fetch and assign op erations can b e dened to act on an arrayentry sp ecied

by a given index and a variantofinit can b e dened to initialise all entries in an array

to a given value

fetch Ix ST Val

Str

fetch i a v  a j v index i a

ST assign Ix Val

assign i v a  update i v a

init Val ST x x

Id

init v x x j x  a x newarray v 

A Str comprehension is used in fetch to force the entry from a to b e fetched b efore a is

made available for further access this is essential in order for it to b e safe to up date a by

overwriting

Now saywe make ST into an abstract data typ e such that the only op erations on

ST ST ST

values of typ e ST are map unit join fetch assign and init It is straightforward

to showthateach of these op erations when passed the sole p ointer to an array returns

as its second comp onent the sole p ointer to an array Since these are the only op erations

that may b e used to build a term of typ e ST this guarantees that it is safe to implement

the assign op eration byoverwriting the sp ecied arrayentry

The key idea here is the use of the abstract data typ e Monad comprehensions are not

essential for this to work they merely provide a desirable syntax

Example Interpreter

Consider building an interpreter for a simple imp erative language The store of this

language will b e mo delled by a state of typ e Arr sowe will take Ix to b e the typ e of

variable names and Val to b e the typ e of values stored in variables The abstract syntax

for this language is represented by the following data typ es

data Exp Var Ix j Const Val j Plus Exp Exp

data Com Asgn Ix Exp j Seq Com Com j If Exp Com Com

data Prog Prog Com Exp 

An expression is a variable a constant or the sum of two expressions a command is an

assignment a sequence of two commands or a conditional and a program consists of a

command followed by an expression

Aversion of the interpreter in a pure functional language is shown in Figure The

interpreter can b e read as a denotational semantics for the language with three semantic

functions

exp Exp Arr Val 

com Com Arr Arr 

prog Prog Val 

The semantics of an expression takes a store into a value the semantics of a command

takes a store into a store and the semantics of a program is a value A program consists of

a command followed by an expression its value is determined by applying the command

to an initial store where all variables have the value and then evaluating the expression

in the context of the resulting store

The interpreter uses the array op erations newarray index andupdate As it happ ens

it is safe to p erform the up dates in place for this program but to discover this requires

using one of the sp ecial analysis techniques cited in the intro duction

The same interpreter has b een rewritten in Figure using state transformers The

semantic functions nowhavethetyp es

exp Exp ST Val 

com Com ST 

prog Prog Val 

The semantics of an expression dep ends on the state and returns a value the semantics

of a command transforms the state only the semantics of a program as b efore is just

tics of an expression might alter the state avalue According to the typ es the seman

although in fact expressions dep end the state but do not change it we will return to this

problem shortly

The abstract data typ e for ST guarantees that it is safe to p erform up dates indicated

by assign in place no sp ecial analysis technique is required It is easy to see how

the monad interpreter can b e derived from the original and using the denitions given

earlier the pro of of their equivalence is straightforward

The program written using state transformers has a simple imp erative reading For

instance the line

ST

com Seqc c j com c  com c

can b e read to evaluate the command Seqc c rst evaluate c and then evaluate

c The typ es and the use of the ST comprehension make clear that these op erations

transform the state further that the values returned are of typ e makes it clear that

only the eect on the state is of interest here

One drawback of this program is that it intro duces to o much sequencing The line

ST

exp Plus e e v v j v exp e  v exp e

can b e read to evaluate Plus e e rst evaluate e yielding the value v then evaluate

e yielding the value v thenadd v and v This is unfortunate it imp oses a spurious

ordering on the evaluation of e and e the original program implies no such ordering

The order do es not matter b ecause although exp dep ends on the state it do es not change

it But as already noted there is no way to express this using just the monad of state

transformers To remedy this we will intro duce a second monad that of state readers

State readers

Recall that the monad of state transformers for a xed typ e S of states is given by

typ e ST x S x  S 

The monad of state readers for the same typ e S of states is given by

typ e SR x S x

SR Id

b b

map f x s fx j x xs

SR

unit x s x

SR Id

b b

b b b b

join x s x j x xs x xs 

b

x isavariable of typ e ST x A state reader of Here x isavariable of typ e SR x just as

typ e x takes a state and returns a value of typ e x but no new state The unit takes

the value x into the state transformer s x that ignores the state and returns x We

have that

SR Id

b b b b

x  y j x x  y y s x  y j x xs y ys 

b b

This applies the state readers x and y to the state s yielding the values x and y which

are returned in a pair

It is easy to see that

SR SR

b b b b

x  y j x x  y y x  y j y y  x x 

b b

so that the order in which x and y are computed is irrelevant A monad with this prop erty

is called commutative since it follows that

SR SR

t j p  q t j q  p

for any term t and any qualiers p and q suchthat p binds no free variables of q and

viceversa Thus state readers capture the notion of order indep endence that we desire

for expression evaluation in the interpreter example

Two useful op erations in this monad are

fetch SR S

fetch s s

ro SR x ST x

Id

b b

ro x s x  s j x xs 

The rst is the equivalent of the previous fetch butnow expressed as a state reader rather

to the corresp onding state than a state transformer The second converts a state reader in

transformer one that returns the same value as the state reader and leaves the state

unchanged The name ro abbreviates read only

In the sp ecic case where S is the arraytyp e Arr we dene

fetch Ix SR Val

fetch i a index i a 

In order to guarantee the safety of up date byoverwriting it is necessary to mo dify two

of the other denitions to use Str comprehensions rather than Id comprehensions

SR Str

b b

map f x a fx j x xa

Str

b b

ro x a x  a j x xa

These corresp ond to the use of an Str comprehension in the ST version of fetch

Thus for arrays the complete collection of op erations on state transformers and state

readers consists of

fetch Ix SR Val 

assign Ix Val ST 

ro SR x ST x 

init Val ST x x 

SR SR SR ST ST ST

together with map unit join and map unit join These ten op erations

should b e dened together and constitute all the ways of manipulating the twomutually

dened abstract data typ es SR x and ST x It is straightforward to show that each

op eration of typ e SR when passed an array returns a value that contains no p ointer to

that array once it has b een reduced to weak head normal form WHNF and that each

op erations of typ e ST when passed the sole p ointer to an array returns as its second

comp onent the sole p ointer to an array Since these are the only op erations that maybe

used to build values of typ es SR and ST this guarantees that it is safe to implement the

assign op eration byoverwriting the sp ecied arrayentry The reader maycheck that the

SR

Str comprehensions in map and ro are essential to guarantee this prop erty

Returning to the interpreter example we get the new version shown in Figure The

only dierence from the previous version is that some o ccurrences of ST havechanged to

SR and that ro has b een inserted in a few places The new typing

exp Exp SR Val

makes it clear that exp dep ends on the state but do es not alter it A pro of that the two

versions are equivalent app ears in Section

The excessive sequencing of the previous version has b een eliminated The line

SR

exp Plus e e v v j v exp e  v exp e

can now b e read to evaluate Plus e e evaluate e yielding the value v and evaluate e

yielding the value v then add v and v The order of qualiers in an SR comprehension

is irrelevant and so it is p erfectly p ermissible to evaluate e and e in any order or even

concurrently

The interpreter derived here is similar in structure to one in Wad which uses a typ e

system based on linear logic to guarantee safe destructive up date of arrays Related typ e

systems are discussed in GH Wad However the linear typ e system uses a let

construct that suers from some unnatural restrictions it requires hyp erstrict evaluation

and it prohibits certain typ es involving functions By contrast the monad approach

requires only strict evaluation and it places no restriction on the typ es This suggests

that a careful study of the monad approachmay lead to an improved understanding of

linear typ es and the let construct

Filters

So far wehave ignored another form of qualier found in list comprehensions the lter

For list comprehensions we can dene lters by

t j b if b then t else 

where b is a b o oleanvalued term For example

x j x    odd x

join x j odd x j x  

join j odd  j odd  j odd

join  

 

Can we dene lters in general for comprehensions in an arbitrary monad M Theanswer

is yes if we can dene for M Not all monads admit a useful denition of but many

do

Recall that comprehensions of the form t are dened in terms of the qualier by

taking t t j and that is a unit for qualier comp osition

t j  q t j q t j q  

Similarlywe will dene comprehensions of the form in terms of a new qualier by

taking t j and we will require that is a zero for qualier comp osition

t j q t j t j q  

Unlike with t j the value of t j is indep endentoft

Recall that for weintro duced a function unit x Mx satisfying the laws

iii map f unit unit f 

join unit id  I

II join map unit id 

and then dened t j unit t

Similarlyfor weintro duce a function

zero y Mx

satisfying the laws

v map f zero zero g 

IV join zero zero 

V join map zero zero 

and dene

t j zerot

Lawv sp ecies that the result of zero is indep endent of its argument and can b e derived

from the typ e of zero again see Rey Wad In the case of lists setting zer oy

makes laws IV andV hold since join and join  This ignores

what happ ens when zero is applied to which will b e considered b elow

Now for a monad with zero we can extend comprehensions to contain a new form of

qualier the lter dened by

t j b if b then t else 

where b is any b o oleanvalued term Recall that laws and were proved by induction

on the form of qualiers we can show that for the new forms of qualiers dened by

and they still hold We also have new laws

t j b  c t j b c 

t j b  q  t j q  b

where b and c are b o oleanvalued terms and where q is any qualier not binding variables

free in b

When dealing with as a p otential value more care is required In a strict language

where all functions including zero are strict there is no problem But in a lazy language

in the case of lists laws v and IV hold but lawV is an inequality join map zero v

zero since join map zero but zero In this case laws are still

valid but law holds only if t j q In the case that t j q law

b ecomes an inequalityt j q  b v t j b  q

As a second example of a monad with a zero consider the strictness monad Str dened

Str

in Section For this monad a zero may b e dened by zero y It is easy to verify

that the required laws hold unlike with lists the laws hold even when zero is applied to

Str

For example x j x returns one less than x if x is p ositive and otherwise

Monad morphisms

If M and N are two monads then h Mx Nx is a monad morphism from M to N if

it preserves the monad op erations

M N

h map f map f h 

M N

h unit unit 

M N

join h  h join

M N

y the rst equation where h h map h map h h the two comp osites are equal b

Dene the eect of a monad morphism on qualiers as follows

h 

h x u x hu

h p  q hp hq

It follows that if h is a monad morphism from M to N then

M N

h t j q t j hq

for all terms t and qualiers q The pro of is a simple induction on the form of qualiers

M

As an example it is easy to check that unit x Mx is a monad morphism from

Id to M It follows that

Id M M M

t j x u t j x u 

This explains a trick o ccasionally used by functional programmers where one writes the

qualier x u inside a list comprehension to bind x to the value of u that is to achieve

the same eect as the qualier x u in an Id comprehension

As a second example the function ro from Section is a monad morphism from SR

to ST This can b e used to prove the equivalence of the twointerpreters in Figures

ST SR

and Write exp Exp ST Val and exp Exp SR Val for the versions in the

two gures The equivalence of the twoversions is clear if we can showthat

SR ST

ro exp exp 

The pro of is a simple induction on the structure of expressions If the expression has the

form Plus e e wehavethat

SR

ro exp Plus e e

SR

funfolding exp g

SR SR SR

ro v v j v exp e  v exp e

fby g

SR SR ST

v v j v ro exp e  v ro exp e

fhyp othesisg

ST ST ST

v v j v exp e  v exp e

ST

ffolding exp g

ST

exp Plus e e 

The other two cases are equally simple

All of this extends straightforwardly to monads with zero In this case we also require

M N

that h zero zero dene the action of a morphism on a lter by hb b and observe

that holds even when q contains lters

More monads

This section describ es four more monads parsers expressions inputoutput and contin

uations The basic techniques are not new parsers are discussed in Wad Fai FL

and exceptions are discussed in Wad Spi but monads and monad comprehensions

provide a convenient framework for their expression

Parsers

The monad of parsers is given by

typ e Parse x String List x  String

List Parse

f x i fx i j x  i xi map

Parse List

unit x i x  i

Parse List

join x i x  i j x  i xi x  i xi 

Here String is the typ e of lists of Char Thus a parser accepts an input string and returns

a list of pairs The list contains one pair for each successful parse consisting of the value

parsed and the remaining unparsed input An empty list denotes a failure to parse the

input Wehave that

Parse List

x y x y

 y i x  y  i j x  i i  y  i i  x  y j x

This applies the rst parser to the input binds x to the value parsed then applies the

second parser to the remaining input binds y to the value parsed then returns the pair

x  y asthevalue together with input yet to b e parsed If either x or y fails to parse its

input returning an empty list then the combined parser will fail as well

There is also a suitable zero for this monad given by

Parse List

zero y i 

Parse

Thus is the parser that always fails to parse the input It follows that wemay use

lters in Parse comprehensions as well as in List comprehensions

The alternation op erator combines two parsers

Parse x Parse x Parse x

x y i xiyi

Here is the op erator that concatenates two lists It returns all parses found by the

rst argumentfollowed by all parses found by the second

The simplest parser is one that parses a single character

next Parse Char

List

next i head i  tail i j not nul l i 

Here wehavea List comprehension with a lter The parser next succeeds only if the

input is nonempty in which case it returns the next character Using this wemay dene

a parser to recognise a literal

lit Char Parse

Parse

lit c j c next  c c 

Nowwehavea Parse comprehension with a lter The parser lit c succeeds only if the

next character in the input is c

As an example a parser for fully parenthesised lamb da terms yielding values of the

typ e Term describ ed previously can b e written as follows

term Parse Term

Parse

term Var x j x name

Lam x t j lit  lit  x name  lit 

Parse

t term  lit

Parse

App t u j lit  t term  u term  lit

name Parse Name

Parse

name c j c next  a c  c z 

Here for simplicity it has b een assumed that names consist of a single lowercase letter

Char and that and are b oth characters so Name

Exceptions

The typ e Maybex consists of either a value of typ e x written Just x or an exceptional

value written Nothing

data Maybex Just x j Nothing 

The names are due to Spivey Spi The following op erations yield a monad

Maybe

map f Just x Just fx

Maybe

map f Nothing Nothing

Maybe

unit x Just x

Maybe

join Just Just x Just x

Maybe

join Just Nothing Nothing

Maybe

join Nothing Nothing 

Wehavethat

Maybe

x  y y x  y j x

returns Just x  y if x is Just x and y is Just y and otherwise returns Nothing

There is also a suitable zero for this monad given by

Maybe

zero y Nothing 

Maybe Maybe Maybe

Hence Nothing and x Just x For example x j x

returns one less than x if x is p ositive and Nothing otherwise

Two useful op erations test whether an argument corresp onds to a value and if so

return that value

exists Maybex Bool

exists Just x True

exists Nothing False

the Maybex x

the Just x x 

Observethat

Maybe

the x j exists x x

x MaybexIfwe assume that the Nothing itiseasilychecked that the is for all

a monad morphism from Maybe to Str Wehavethat

Maybe Str

the x j x x j x

as an immediate consequence of the monad morphism law This mapping emb o dies the

common simplication of considering error values and to b e identical

The biasedchoice op erator cho oses the rst of two p ossible valuesthatiswell dened

Maybex Maybex Maybex

x y if exists x then x else y 

The op eration is asso ciativeandhasNothing as a unit It app eared in early versions

of ML GMW and similar op erators app ear in other languages As an example of its

use the term

Maybe Maybe

the x j x

returns the predecessor of x if it is nonnegative and zero otherwise

In Wad it was prop osed to use lists to represent exceptions enco ding a value x by

the unit list and an exception by the empty list This corresp onds to the mapping

list Maybex List x

List

list Just x x

List

list Nothing

which is a monad morphism from Maybe to List Wehave that

x y list x list y  list

where is the sublist relation Thus exception comprehensions can b e represented by list

comprehensions and biased choice can b e represented by list concatenation The argu

mentinWad that list comprehensions provideaconvenient notation for manipulating

exceptions can b e mapp ed via this morphism into an argumentinfavour of exception

comprehensions

Input and output

Fix the input and output of a program to b e strings eg the input is a sequence of

characters from a keyb oard and the output is a sequence of characters to app ear on a

screen The input and output monads are given by

typ e In x String x  String

typ e Out x x  String String 

The input monad is a function from a string the input to the program and to a pair of

avalue and a string the input to the rest of the program The output monad is a pair

of a value and a function from a string the output of the rest of the program to a string

the output of the program

The input monad is identical to the monad of state transformers xing the state to

b e a string and the op erations map unit andjoin are identical to those in the state

transformer monad Two useful op erations in the input monad are

eof In Bool

eof i nul l i  i

read In Char

i head i  tail i  read

The rst returns true if there is more input to b e read the second reads the next input

character

The output monad is given by

Out Id

b b

map f x fx ot j x  ot x

Out

unit x x o o

Out Id

b b

b b b b

join x x  ot ot j x  ot x  x  ot x 

The second comp onent of the pair is an output transformer whichgiven the output of

the rest of the program pro duces the output of this part The unit pro duces no output of

its own so its output transformer is the identity function The join op eration comp oses

two output transformers A useful op eration in the output monad is

write Char Out

write c o c o 

This adds the character to b e written onto the head of the output list

Alternative denitions of the output monad are p ossible but these do not b ehaveas

well as the formulation given ab ove One alternative treats output as a state transformer

typ e Out x String x  String 

taking map unit and join as in the state transformer monad The write op eration is

now

write Char Out

write c o  c o 

This formulation is not so go o d b ecause it is to o strict output will not app ear until the

program terminates Another alternativeis

typ e Out x x  String

Id Out

b b

f x fx o j x  o x map

Out

unit x x 

Out Id

b b

b b b b

join x x  o o j x  o x  x  o x

write c  c 

This formulation is also not so go o d b ecause the time to p erform the concatenation

op erations is quadratic in the size of the output in the worst case

Finally the output and input monads can b e combined into a single monad

String  typ e InOut x String x  String  String

Suitable denitions of map unit andjoin are left to the reader Useful op erations on

this monad are

in In x InOut x

Id

in x i x  i o o j x  i xi

out Out x InOut x

Id

b b

out x i x  i  ot j x  ot x

fun InOut String String

Id

fun x i ot j  i  ot xi 

The rst two are monad morphisms from In and Out to InOut they take inputonly

and outputonly op erations into the inputoutput monad The last takes a value into the

inputoutput monad into a function from the input to the output

Continuations

Fixatyp e R of results The monad of continuations is given by

typ e Cont x x R R

Cont

map f x k x x k fx

Cont

unit x k kx

Cont

join x k x x x x kx

Acontinuation of typ e x takes a continuation function k x R which sp ecies how

to takea value of typ e x into a result of typ e R and returns a result of typ e R The unit

takesavalue x into the continuation k kx that applies the continuation function to

the given value Wehave that

Cont

x  y j x x  y y k x x y y k x  y 

x bindx to the result then evaluate y bindy to This can b e read as follows evaluate

the result then return the pair x  y

A useful op eration in this monad is

cal lcc x Cont y Cont x Cont x

cal lccg k g x k kx k 

This mimics the call with currentcontinuation or cal l cc op eration p opular from

Scheme RC For example the Scheme program

cal l cc lambda esc  x if yesc y

translates to the equivalent program

Cont Cont

y then esc else y  cal lcc esc x z j z if

Both of these programs bind esc to an escap e function that returns its argument as the

value of the entire cal lcc expression They then return the value of x divided by y or

return if y is zero

Translation

In Section wesaw that a function of typ e U V in an impure functional language

that manipulates state corresp onds to a function of typ e U ST V in a pure functional

language The corresp ondence was drawn in an informal waysowe might ask what

assurance is there that every program can b e translated in a similar way This section

provides that assurance in the form of a translation of calculus into an arbitrary monad

This allows us to translate not only programs that manipulate state but also programs

that raise exceptions call continuations and so on Indeed we shall see that there are

two translations one callbyvalue and one callbyname The target language of b oth

translations is a pure nonstrict calculus augmented with M comprehensions

We will p erform our translations on a simple typ ed lamb da calculus We will use T

U V to range over typ es and K to range over base typ es A typ e is either a base typ e

function typ e or pro duct typ e

T  U  V K j U V j U  V 

We will use t u v to range over terms and x to range over variables A term is either a

variable an abstraction an application a pair or a selection

j snd t  t  u  v x j x v j tu j u  v j fst t

In the following we usually give the case for fst t but omit that for snd t since the two

are nearly identical WewilluseA to range over assumptions which are lists asso ciating

variables with typ es

A x T x T 

n n

We write the typing A t T to indicate that under assumption A the term t has typ e

T The inference rules for welltypings in this calculus are well known and can b e seen

on the left hand sides of Figures and

The callbyvalue translation of lambda calculus into a monad M is given in Figure

The translation of the typ e T is written T and the translation of the term t is written

t The rule for translating function typ es

U V U MV 

ta value of typ e U and returns can b e read a callbyvalue function takes as its argumen

a computation of typ e V This corresp onds to the translation in Section where a

function of typ e U V in the impure source language is translated to a function of

typ e U MV in the pure target language Each of the rules for translating terms has

a straightforward computational reading For example the rule for applications

M

tu y j f t  x u  y fx 

can b e read to apply t to u rst evaluate t call the result f then evaluate u call

the result x then apply f to x call the result y and return y This is what one

would exp ect in a callbyvalue language the argumentisevaluated b efore the function

is applied If

x T x T t T

n n

is a welltyping in the source language then its translation

x T x T t MT

n

n

isawelltyping in the target language Like the arguments of a function the free variables

corresp ond to values while like the result of a function the term corresp onds to a com

putation Figure demonstrates that the callbyvalue translation preserves welltypings

a term that is welltyp ed in the source language translates to one that is welltyp ed in

the target language

The callbyname translation of calculus into a monad M is given in Figure Now

y

the translation of the typ e T is written T and the translation of the term t is written

y

t The rule for translating function typ es

y y y

U V MU MV 

can b e read a callbyname function takes as its argumentacomputation of typ e U and

returns a computation of typ e V The rule for applications

y y y M

tu y j f t  y fu 

can b e read to apply t to u rst evaluate t call the result f then apply f to the term

u call the result y and return y This is what one would exp ect in a callbyname

u is passed unevaluated and is evaluated each time it is used language the argument

The welltyping in the source language given previously now translates to

y

y y y

x MT x MT t MT 

n

n

whichisagainawelltyping in the target language This time b oth the free variables and

the term corresp ond to computations reecting that in a callbyname language the free

variables corresp ond to computations or closures that must b e evaluated each time they

are used Figure demonstrates that the callbyname translation preserves welltypings

In particular the callbyvalue intrepretation in the strictness monad Str of Section

yields the usual strict semantics of calculus whereas the callbyname interpretation in

the same monad yields the usual lazy semantics

If we use the monad of say state transformers then the callbyvalue interpretation

yields the usual semantics of a calculus with assignment The callbyname interpreta

tion yields a semantics where the state transformation sp ecied byavariable o ccurs each

time the variable is accessed This explains why the second translation is titled callby

name rather than callbyneed Of course since the target of b oth the callbyvalue and

callbyname translations is a pure nonstrict calculus there is no problem with exe

ntation cuting programs translated by either scheme in a lazy ie callbyneed impleme

Example Nondeterminism

As a more detailed example of the application of the translation schemes consider a

small nondeterministic language This consists of the calculus as dened ab ove with its

syntax extended to include a nondeterministic choice op erator t and simple arithmetic

t  u  v j u t v j n j u v 

where n ranges over integer constants This language is typ ed just as for lamb da calculus

We assume a base typ e Int and that the additional constructs typ ed as follows for any

typ e T ifu T and v T then u t v T and n Int andifu Int and v Int

then u v Int For example the term

a a a t

has the typ e Int Under a callbyvalue interpretation wewould exp ect this to return

either or ie or whereas under a callbyname interpretation wewould

exp ect this to return or or ie or or or

We will give the semantics of this language byinterpreting the calculus in the set

monad as sp ecied in Section In what follows we will write f t j q g in preference to

Set

the more cumb ersome t j q

The callbyvalue interpretation for this language is provided by the rules in Figure

cho osing M to b e the monad Set together with the rules

u t v u v

n fn g

u v f x y j x u  y v g

These rules translate a term of typ e T in the nondeterministic language into a term

of typ e Set T in a pure functional language augmented with set comprehensions For

example the term ab ove translates to

y j x fa g y fa gg g f y j f fa fx

x f gf g

y fx g

which has the value f  g as exp ected

The callbyname translation of the same language is provided by the rules in Figure

The rules for u t v n and u v are the same as the callbyvalue rules replacing

y

with Now the same term translates to

f y j f fa fx y j x a  y a g g

gf g g y f f

which has the value f   g as exp ected

A similar approach to nondeteminism is taken by Hughes and ODonnell HO

They suggest adding a set typ e to a lazy functional language where a set is actually

represented by a nondeterministic choice of one of the elements of the set The primitive

op erations they provide on sets are just map unit andjoin of the set monad plus set

union to represent nondeterministic choice They address the issue of how such sets

should b ehave with resp ect to and presentanelegant derivation of a nondeterministic

parallel tree search algorithm However they provide no argument that all programs in

a traditional nondeterministic functional language can b e enco ded in their approach

Such an argumentisprovided by the translation scheme ab ove

Example Continuations

As a nal example consider the callbyvalue interpretation under the monad of contin

uations Cont given in Section Applying straightforward calculation to simplify the

Cont comprehensions yields the translation scheme given in Figure which is simply

the continuationpassing style transformation b eloved bymany theorists and compiler

writers Plo AJ

Each of the rules retains its straightforward op erational reading For example the

rule for applications

tu k t f u x fxk

can still b e read to apply t to u rstevaluate t call the result f then evaluate u call

the result x then apply f to x call the result y and return y

A similar calculation on the other translation scheme yields a callbyname version of

continuationpassing style This is less well known but can b e found in Rey Plo

Acknowledgements

I thank Eugenio Moggi for his ideas and for the time he to ok to explain them to me I

bury for his enthusiasm and suggestions And for helpful comments thank John Launch

I thank Arvind Stephen Bevan Olivier Danvy Kevin Hammond John Hughes Karsten

Kehler Holst Michael Johnson Austin Melton Nikhil Andy Pitts

Andre Scedrov Carolyn Talcott Phil Trinder attenders of the Glasgow Summer

Scho ol on Category Theory and Constructive Logic and an anonymous referee

References

AJ A App el and T Jim Contiuationpassing passing style In th ACM

Symposium on Principles of Programming Languages Austin Texas January

Blo A Bloss Up date analysis and the ecient implementation of functional aggre

gates In th Symposium on Languages and Computer

ArchitectureACM London September

BW M Barr and C Wells Triples and Theories Springer Verlag

BW R Bird and PWadler Introduction to Functional Programming Prentice Hall

Fai J Fairbairn Form follows function SoftwarePracticeandExperience

 June

FL R Frost and J Launchbury Constructing natural language interpreters in a

lazy functional language The Computer Journal  April

Gog J A Goguen Higher order functions considered unnecessary for higher or

der programming Technical rep ort SRICSL SRI International January

GL D K Giord and J M Lucassen Integrating functional and imp erative pro

gramming In ACM ConferenceonLispandFunctional Programming pp

Cambridge Massachusetts August

GH J Guzman and P Hudak Singlethreaded p olymorphic lamb da calculus In

IEEE Symposium on Logic in Computer Science Philadelphia June

GMW M Gordon R Milner and C Wadsworth Edinburgh LCF LNCS Springer

Verlag

Hol S Holmstrom A simple and ecientway to handle large data structures in

applicative languges In Proceedings SERCChalmers Workshop on Declarative

Programming University College London

Huda P Hudak A semantic mo del of reference counting and its abstraction detailed

summary In ACM Conference on Lisp and Functional Programming pp

Cambridge Massachusetts August

ersion HMT R Harp er R Milner and M Tofte The denition of Standard ML v

Rep ort ECSLFCS Edinburgh University Computer Science Dept

Hudb P Hudak Arrays nondeterminism sideeects and parallelism a functional

p ersp ective In J H Fasel and R M Keller editors Workshop on Graph Re

ductionSanta Fe New Mexico Septemb erOctob er LNCS Springer

Verlag

Hug J Hughes Why functional programming matters The Computer Journal

 April

HO J Hughes and J ODonnell Expressing and reasoning ab out nondeterministic

functional programs In K Davis and J Hughes editors Functional Program

ming Glasgow Glasgowworkshop Fraserburgh August Work

shops in Computing Springer Verlag

HPW P Hudak S Peyton Jones and PWadler editors Report on the Programming

Language Haskel l Version Technical rep ort Yale University and Glasgow

University August

LS J Lambek and P Scott Introduction to Higher Order Categorical Logic Cam

bridge University Press

Mac S Mac Lane Categories for the Working Mathematician SpringerVerlag

Mil R Milner A prop osal for Standard ML In ACM Symposium on Lisp and

Functional Programming Austin Texas August

MT I Mason and C Talcott Axiomatising op erational equivalence in the presence

of side eects In IEEE Symposium on Logic in Computer Science Asilomar

California June

Moga E Moggi Computational lamb dacalculus and monads In IEEE Symposium on

Logic in Computer Science Asilomar California June A longer version

is available as a technical rep ort from the UniversityofEdinburgh

Mogb E Moggi An abstract view of programming languges Course notes University

of Edinburgh

Plo G Plotkin Callbyname callbyvalue and the calculus Theoretical Com

puter Science

RC J Rees and W Clinger eds The revised rep ort on the algorithmic language

Scheme ACM SIGPLAN Notices 

uation semantics Rey J C Reynolds On the relation b etween direct and contin

In Col loquium on Automata Languages and Programming Saarbruc ken July

August LNCS SpringerVerlag

Rey J C Reynolds Typ es abstraction and parametric p olymorphism In R E

A Mason editor Information Processing NorthHolland Ams

terdam

Sch D A Schmidt Detecting global variables in denotational sp ecications ACM

Transactions on Programming Languages and Systems 

Spi M Spivey A functional theory of exceptions Science of Computer Program

ming  June

Tur D A Turner Recursion equations as a In J Darling

ton P Henderson and D A Turner editors Functional Programming and its

Applications Cambridge University Press

Tur D A Turner Miranda A nonstrict functional language with p olymorphic

typ es In Proceedings of the nd International ConferenceonFunctional Pro

gramming Languages and Computer Architecture NancyFrance Septem ber

LNCS Springer Verlag

Wad PWadler How to replace failure by a list of successes In nd Symposium

on Functional Programming Languages and Computer Architecture Nancy

Septemb er LNCS SpringerVerlag

Wad PWadler List comprehensions In S L Peyton Jones The Implementation of

Functional Programming Languages Prentice Hall

Wad PWadler Theorems for free In th Symposium on Functional Programming

Languages and Computer ArchitectureACM London Septemb er

Wad PWadler Linear typ es can change the world In M Broy and C Jones

editors Programming Concepts and Methods IFIP Working Conference Sea

of Gallilee Israel April North Holland

Wad PWadler Is there a use for linear logic In Conference on Partial Evalua

tion and SemanticsBasedProgram Manipulation PEPMACM New Haven

Connecticut June

datatyp e Term Var of Name j Lam of Name Term j App of Term Term

fun rename t let val N ref

fun newname let val n N

val N n

in mkname n

end

fun renamer Var x Var x

j renamer Lam x t let val x newname

renamer t in Lam x subst x x

end

j renamer App t u App renamer t renamer u

in renamer t

end

Figure Renaming in an impure functional language Standard ML

data Term Var Name j Lam Name Term j App Term Term

newname Int Name Int

newname n mkname n n

renamer Term Int Term Int

renamer Var x n Var x n

renamer Lam x t n let x n newname n

t n renamer t n

in Lam x subst x xt n

renamer App t u n let t n renamer t n

u n renamer u n

in App t u n

rename Term Term

rename t let t n renamer t in t

Figure Renaming in a pure functional language Haskell

data Term Var Name j Lam Name Term j App Term Term

newname ST Name

ST

newname mkname n j n fetch assign n

renamer Term ST Term

ST

renamer Var x Var x

ST

renamer Lam x t Lam x subst x xt j x newname t renamer t

ST

renamer App t u App t u j t r enamer t u renamer u

rename Term Term

rename t init renamer t

Figure Renaming with the monad of state transformers

exp Exp Arr Val

exp Var i a index i a

exp Const v a v

exp Plus e e a exp e a exp e a

com Com Arr Arr

com Asgn i e a update i exp e a a

com Seqc c a com c com c a

a else com c a com If e c c a if exp e a then com c

prog Prog Val

prog Progce exp e com c newarray

Figure Interpreter in a pure functional language

exp Exp ST Val

ST

exp Var i v j v fetch i

ST

exp Const v v

ST

exp Plus e e v v j v exp e v exp e

com Com ST

ST

com Asgn i e j v exp e assign i v

ST

com c com Seqc c j com c

ST

com If e c c j v exp e if v then com c else com c

prog Prog Val

ST

prog Progce init v j com c v exp e

Figure Interpreter with state transformers

exp Exp SR Val

SR

exp Var i v j v fetch i

ST

exp Const v v

SR

exp Plus e e v v j v exp e v exp e

com Com ST

ST

com Asgn i e j v ro exp e assign i v

ST

com Seqc c j com c com c

ST

com If e c c j v ro exp e if v then com c else com c

prog Prog Val

ST

prog Progce init v j com c v ro exp e

Figure Interpreter with state transformers and readers

Typ es

K K

U V U MV

U  V U  V

Terms

M

x x

M

x v x v

M

tu y j f t  x u  y fx

M

u  v x  y j x u  y v

M

fst t fst z j z t

Assumptions

x T x T x T x T

n n n

n

Typings

A t T A t MT

Figure Callbyvalue translation

M

A x T x T A  x T x MT

A x U v V A  x U v MV

M

A x v U V A x v M U MV

A t U V A t M U MV

A u U A u MU

M

A tuV A y j f t  x u  y fx MV

A u U A u MU

A v V A v MV

M

A u  v U  V A x  y j x u  y v M U  V

A t U  V A t M U  V

M

A fst t U A fst z j z t MU

Figure The callbyvalue translation preserves welltyping

Typ es

y

K K

y y y

U V MU MV

y y y

U  V MU  MV

Terms

y

x x

y y M

x v x v

y y y M

tu y j f t  y fu

y y y M

u  v u  v

y y M

fst t x j z t  x fst z

Assumptions

y

y y

x MT x T x T x MT

n n n

n

Typings

y y y y

A t T A t MT

Figure Callbyname translation

y y y y

A x T x T A  x MT x MT

y y y y y

A x U v V A  x MU v MV

y y y M y y

A x v U V A x v M MU MV

y y y y y

A t U V A t M MU MV

y y y y

A u U A u MU

y y y y M y

A tuV A y j f t  y fu MV

y y y y

A u U A u MU

y y y y

A v V A v MV

y y y y M y y

A u  v U  V A u  v M MU  MV

y y y y y

A t U  V A t M MU  MV

y y y M y

A fst t U A x j z t  x fst z MU

Figure The callbyname translation preserves welltyping

x k kx

x v k k x v

tu k t f u x fxk

u  v k u x v y k x  y

fst t k t z k fst z

Figure Callbyvalue continuationpassing style transformation

y

x x

y y

x v k k x v

y y y

tu k t f fu k

y y y

u  v k k u  v

y y

fst t k t z fst z k

Figure Callbyname continuationpassing style transformation