Typ ed Closure Conversion

y

Yasuhiko Minamide Greg Morrisett Rob ert Harp er

Research Institute for Mathematical Sciences Scho ol of Computer Science Scho ol of Computer Science

Kyoto University Carnegie Mellon University Carnegie Mellon University

Kyoto Japan Pittsburgh PA Pittsburgh PA

nankurimskyotouacjp jgmorriscscmuedu rwhcscmuedu

data Functions with free variables are replaced by co de ab Abstract

stracted on an extra environment parameter Free variables

Closureconversion is a program transformation used by

in the b o dy of the function are replaced by references to the

compilers to separate co de from data Previous accounts

environment The abstracted co de is partially applied to an

of closure conversion use only untyped target languages Re

explicitly constructed environmentproviding the bindings

cent studies show that translating to typed target languages

for these variables This partial application of the co de to

is a useful metho dology for building compilers b ecause a

its environment is in fact susp ended until the function is ac

compiler can use the typ es to implement ecient data rep

tually applied to its argument the susp ended application

resentations calling conventions and tagfree garbage col

called a closure is a data structure consisting of a piece of

lection Furthermore typ ebased translations facilitate se

pure co de and a representation of its environment

curity and debugging through automatic typ e checking as

A critical decision in closure conversion is the choice

well as correctness arguments through the metho d of logical

of representation for the environment whether to use a

relations

at FAMlike linked CAMlikeorhybrid represen ta

We present closure conversion as a typ edirected and

tion The choice of representation is inuenced byade

typ epreserving translation for b oth the simplytyp ed and

sire to minimize closure creation time the space consumed

the p olymorphic calculus Our translations are based on

by the environment and the time to access a variable in

a simple closures as ob jects principle higherorder func

the environment An imp ortant prop erty of closure

tions are viewed as ob jects consisting of a single metho d

conversion is that the representation of the environmentis

the co de and a single instance variable the environment

private to the closure This aords considerable exibility

In the simplytyp ed case the PierceTurner mo del of ob

in the representation of environments and is thus exploited

ject typing where ob jects are packages of existential typ e

to go o d advantage by Shao and App el and Wand and

suces In the p olymorphic case more careful tracking of

Steckler

typ e sharing is required We exploit a variant of the Harp er

Previous accounts consider closure conversion as a trans

Lillibri dge translucenttyp e formalism to characterize the

formation to untyped terms even if the source language is

typ es of p olymorphi c closures

typ ed This is adequate for compilers that

make little or no use of typ es in the back end or at run

time However when compiling typ ed languages it is often

Intro duction

advantageous to propagate typ e information through each

stage of the compiler and to make use of typ es at link or

Closureconversion is a program

even run time For example Leroys representation analy

transformation that achieves a separation b etween co de and

sis uses typ es to determine pro cedure calling conven

This researchwas sp onsored in part by the Advanced Research

tions and Ohoris record compilation uses a representa

Pro jects Agency CSTO under the title The Fox Pro ject Advanced

tion of typ es at run time to access comp onents of a record

Languages for Systems Software ARPA Order No C issued

Compilation strategies for p olymorphic languages suchas

by ESCENS under Contract No FC and in part

those prop osed by Morrison et al and Harp er and Mor

by the National Science Foundation under Grant No CCR

and in part by the Isaac Newton Institute for Mathematical Sciences

risett rely on analyzing typ es at run time to supp ort

Cambridge England The views and conclusions contained in this

unboxed representations and nonparametric op erators in

do cument are those of the authors and should not b e interpreted as

cluding printing and structural equalityTagfree garbage

representing ocial p olicies either expressed or implied of ARPA

collection for b oth monomorphic and p olymor

or the US Government Any opinions ndings and conclusions

or recommendations expressed in this material are those of the au

phic programming languages relies on analyzing typ es at

thors and do not necessarily reect the views of the National Science

run time to determine the size and la yout of ob jects in the

Foundation

heap To supp ort any of these implementation strategies

y

This researchwas p erformed while the rst author was visiting

it is necessary to propagate typ e information through clo

the Fox Pro ject at Carnegie Mellon University

sure conversion and into the generated co de The purp ose

of this pap er is to demonstrate how this can b e done in b oth

a simplytyp ed and a p olymorphic setting

We present closure conversion as an example of a type

directed and typepreserving translation In general such

the companion technical rep ort translations transform b oth a term and its typ e p ossibly

relying on typ e information to guide the translation Thus

Closure conversion is discussed in descriptions of various

each stage of the compiler can b e viewed as a typ epreserving

functional language compilers It is sim

translation b etween typ ed intermediate languages Exam

ilar to lifting in that it eliminates free variables in

ples of such translations havebeengiven byLeroy

the b o dies of abstractions but diers by making the rep

Ohori Harp er and Lillibri dge and Harp er and Mor

resentation of the environment explicit as a data structure

risett In contrasttotyp efree compilation strategies

Making the environment explicit is imp ortant b ecause it ex

these translations make essential use of typ e information

poses environment construction and variable lo okup to an

during translation to increase the time or space eciency of

optimizer Furthermore Shao and App el show that not all

programs In addition to the practical advantages of this ap

environment representations are safe for space and

proach typ edirected translation also facilitates the work of

thus cho osing a go o d environment representation is an im

the compiler writer In particular the typing prop erties of

p ortant part of compilation Wand and Steckler have

the intermediate co de may b e exploited to give clear concise

wo optimizations of the basic closure conversion consider t

pro ofs of compiler correctness through the metho d of logical

strategy called selective and lightweight closure conversion

relations Furthermore the intermediate

and provide a correctness pro of for each of these in an un

co de of the compiler can b e mechanicall y typ edchecked

typ ed setting Hannan recasts Wands work into a typ ed

an imp ortant debugging to ol for the compiler writer Fi

setting and provides correctness pro ofs for one of Wands

nallycheckable typ ed intermediate languages are a promis

optimizations Hannans translation like ours is given as a

ing technique for ensuring safety prop erties of programs in

deductive system but he do es not consider the imp ortant

a distributed environment

issue of environment representation preferring an abstract

account instead nor do es he consider the typing prop erties

We describ e closure conversion for the simplytyp ed

of the closureconverted co de Finally neither Wand nor

calculus and the predicative fragment of the p olymorphic

Hannan consider closure conversion under a typ epassing

calculus In eachcasewe present closure conversion in

interpretation of p olymorphism

two stages The rst stage called abstract closureconver

yp edirected translation to an intermediate lan sionisa t

The remainder of this pap er is organized as follows In

guage with a primitive notion of closures We describ e the

Section we giveanoverview of closure conversion and

translation as a deductive system where the choice of en

the typing issues involved for the simplytyp ed calculus

vironment representations may b e indep endently made for

In Section weprovide the details of our typ epreserving

each closure We argue that various representations consid

transform for the simplytyp ed case In Section we givean

ered in the literature such as the FAM or CAM as

overview of closure conversion and the typing issues involved

well as hybrid representations can all b e explained in

for the predicative fragment of the p olymorphic calculus

this uniform framework We establish the correctness of the

The formal development of this conversion is given in Section

translation once for all environment representations

The second stage called closurerepresentationisan

other typ edirected translation where closures are imple

mented in terms of generic typ ed calculus primitives The

Overview of SimplyTyp ed Closure Con

main idea is to represent closures as objects consisting of

a single metho d the co de and a single instance variable

version

the environment We show that in the simplytyp ed case

The main ideas of closure conversion are illustrated by con

Pierce and Turners typ e discipli ne for ob jectoriented pro

sidering the following ML program

gramming may b e used to characterize the typ es of clo

sures In particular we use existential typ e abstraction to

let val x

ensure the privacy of environment representation in much

val y

the same way that Pierce and Turner hide the representa

val z

tion typ es of instance variables In the p olymorphic case

val f w x y w

wemust use a more sophisticated typ e discipli ne in order

in

to track critical typ e sharing relationships within the clo

f

sure To this end we exploit a variantofthetransluc ent

end

type or manifest type formalism Our closures as

ob jects mo del provides an interesting counterp ointtothe

The function f contains free variables x and yWemay

more familiar ob jects as closures prop osal intro duced by

eliminate references to these variables from the b o dy of f

Reddy

by abstracting an environment env and replacing x and y by

We prove the correctness of b oth the abstract closure

references to the environment In comp ensation a suitable

conversion and the closure representation stages using the

environmentcontaining the bindings for x and y must b e

metho d of logical relations The main idea is to dene a

passed to f b efore it is applied This leads to the following

typ eindexed family of simulation relations that establish a

translation

corresp ondence b etween the source and target terms of the

let val x

translation Once a suitable system of relations has b een

val y

dened it is relatively straightforward to proveby induction

val z

on the denition of the compilation relation that the source

val f env w x env y env w

and target of the translation are related From this wemay

fxx yyg

conclude that a closed program and its translation evaluate

in

to the same result Due to lack of space we omit the pro ofs

f

of correctness here However full details may b e found in end

But since code has a typeoftheform References to x and y in the b o dy of f are replaced by where

ve

pro jections eld selections x and y that access the corre is the typ e of the environment env the closure as a whole

ve

sp onding comp onent of the environment Since the co de for would havetyp e exp osing the typ e of

ve ve

f is closed it may b e hoisted out of the enclosing denition the environment As a result this translation do es not in

and dened at the toplevel We ignore this hoisting phase general preservetyp es For example consider the following

and instead concentrate on the pro cess of closure conversion ML source program with typ e int int

In the preceding example the environment contains bind

let val y

ings only for x and y and is thus as small as p ossible Since z

in

is in scop e it is also sensible to include z in the environment

if true then

of f resulting in the following co de

x xy

let val x else

val y z z

val z end

val f env w x env y env w

Closure converting this expression and representing the clo

fxx yy zzg

sures as pairs yields

in

f

let val y

end

in

if true then

In the examples ab ove weusedaatFAMlike rep

env x x yenv fyyg

resentation of the environment as a record with one eld for

else

eachvariable Alternatively we could cho ose a linked CAM

env z z fg

like representation in which each binding is a separate

end

frame attached to the front of the remaining bindings This

idea leads to the following translation

This program fails to typ echeck b ecause the thenclause of

intg the conditional has typ e fyintgint int fy

let val x

whereas the elseclause has typ e fg int int fg

val y

If typ es are to b e preserved by closure conversion the

val z

representation of the environmentmust b e hidden This

val f env w

maybeachieved through the use of existential typ es

xlinklink env

whose typing rules are given in Figure Brieythepack

ylink env w

construct packages a typ e with a term e abstracting cer

zz linkfyy linkfxxggg f

tain o ccurrences of in the typ e of e as the typ e variable t

in

The open op eration extracts the contents of a package for

f

use within a xed scop e holding the typ e comp onent of the

end

package abstract See Mitchell and Plotkins article for

The linked representation facilitates environment sharing further discussion of existential typ es

but accessing a variable requires link traversals prop ortional Using existentials wemay hide the typ e of the environ

to the nesting depth of the variable in the environment The mentby abstracting it from the typ e of the closure itself

linked representation also supp orts constanttime closure Sp ecicall y a closure of typ e is represented bya

creation but this requires reusing the currentenvironment package of the form

Reusing the currentenvironment can result in unnecessary

pack with code env as t t t

bindings in the environment suchasz ab ove leading to ve ve ve ve

space leaks

with typ e t t t Applying this to the

ve ve ve

These simple translations fail to delay the application of

example of the conditional expression given ab ove we obtain

the co de to its environment under callbyvalue evaluation

the translation

A natural representation of a delayed application or closure

is an ordered pair code env consisting of the co de to

let val y

gether with its environment Application of a closure to

in

an argument pro ceeds by pro jecting the co de part from the

if true then

closure and then applying it simultaneousl y to b oth the en

pack fyintg with env x xyenvfyyg

vironment and the argument according to some calling con

as t t int int t

ve ve ve

vention For example

else

pack fg with env z z fg

let val x

as t t int int t

ve ve ve

val y

end

val z

val code env w xenv yenv w

It is easy to see that the typ es of the clauses of the condi

val env fxx yyg

tional agree and that the translation has typ e t t

ve ve

val f code env

int int t

ve

in

With closures represented as packages of existential typ e

f f

application s of the form ee are translated as follows end

e t

e t

ftg fx ge

t FTV t

pack with e as t t

open e as t with x in e

Figure Typing Rules for Existentials

open e as t with z t t In the intro duction we informally presented a closure as a

ve ve ve

in partial application of co de to an environment with the in

z z e tention that this applicati on is delayed until the closure is

end applied to an argument To make this precise weintro

duce an explicit closure form written hhe e ii where e is

ve

That is the package e is op ened holding the environment

the co de of the closure and e is its environment Notice

ve

representation abstract and the co de part is simultaneously

that closures are distinguish ed from applicatio ns of func

applied to b oth the environment and the argumentofthe

tions to arguments which are written in the usual wayby

application

juxtap osition To capture the restriction that the co de part

of a closure should b e closed weintro duce a sp ecial co de

AFormal Account of SimplyTyp ed Clo

typ e code consisting of closed terms of the form

ve

x x ewhich abstract b oth an environment and

ve ve

sure Conversion

an argument

cl

The typing rules for are standard except for co de and

In this section we present the details of closure conversion for

closures whose rules are given as follows

the callbyvalue simplytyp ed calculus We break the full

transformation into two stages as outlined in the intro duc

x ge fx

ve ve

tion To simplify the presentation we b egin with a version

x x e code

ve ve ve

of abstract closure conversion that do es not admit sharing

of environments and then consider the general shared envi

e code e

ve ve ve

ronment case separatelyNextwe give the representation

hhe e ii

ve

of closures in terms of existential typ es as sketched in the

preceding section Finallyweprove the correctness of the

The evaluation rules governing closures are given as fol

translations using a logical relations argument

lows

We dene the syntax of the source language as fol

e v e v

lows

hhe e ii hhv v ii

Types b j

e hhx x e v ii e v

ve ve ve

Expressions e c j x j x e j e e

ev x v x v

ve ve

Values v c j x e

e e v

Typ es consist of base typ es b and function typ es Expres

When a closure is applied to an argument the environment

sions consist of constants c of base typ e variables abstrac

and the argument are substituted for the corresp onding vari

tions and application s We use to denote a sequence of

ables and the b o dy of the co de is evaluated

typ e bindings of the form fx x g n where

n n

the x s are distinct variables The judgement e

We dene abstract closure conversion as the typ edirected

i

cl

asserts that the expression e has typ e under the typ e as

translation from to given in Figure We formulate

signment and is derived from the standard typing rules

the translation as a deductive system with judgements of

tics of of the simplytyp ed calculus The dynamic seman

the form xe e and x e where

ve

the language is dened by judgements of the form e v

and are source typ e assignments is a source typ e e is

asserting that the closed expression e evaluates to the value

a source expression and e and e are target expressions

ve

v The judgement is dened by the following standard in

The distingui shed variable x is used to represent the argu

ference rules for callbyvalue evaluation

ment of the nearest enclosing abstraction the variables in

include this abstractions free variables

e x e e v ev x v

v v

The judgementxe e asserts that e is the

e e v

fx ge translation of e under the assumption that

for some The judgementx e asserts

ve

Abstract Closure Conversion

that e is an expression that evaluates to the environment

ve

corresp onding to under the assumption that each binding

We dene the target language for abstract closure conver

cl

in o ccurs in fx g The order of bindings in is

sion as follows

imp ortant b ecause this determines the translation of b oth

Types b j jh ijcode

n ve

environments and free variables

Exps e c j x j e e jhe e ij e j

n i

In practice a multiargument abstraction is used for co de in

x x e jhhe e ii

ve ve

the target language However the p olymorphic case requires a more

Values v c j x x e jhv v ij hhv v ii

ve ve n

complicated construct that abstracts b oth values andtyp es

For uniformitywe use a curried presentation to abstract multiple

The results of this pap er easily extend to other source typ es in

arguments cluding pro ducts and sums

constxc c argxx x env fx x g xx x

n n i i ve

x e xe e xe e xe e

ve

abs app

e x xe hhx j jx e e ii xe e e

ve ve

xx e xx e

n n

fx gx context

i i

xfx x g he e i

n n n

Figure SimplyTyp ed Abstract Closure Conversion

values These relations are dened as follows We use the variable x to hold the environment argu

ve

ment of the currentcodebodyThus we translate free vari

hv v ix vx

n ve

fx x gx

n n

ables to pro jections of x More precisely according to

ve

i x v for i n and x v

i i

i

rule envwe translate a reference to the free variable x

i

found in the ith p osition of the typ e assignment to the ith

Theorem Let If fx ge and

x

pro jection of the variable x On the other hand according

ve

x e e then e e

to rule arg we translate a reference to the argumentofthe

current co de b o dy to the distinguished argumentvariable x

Thus for a closed program of base typ e evaluating the

Under the assumptions x we translate an abstrac

program and its translation yields syntactically equivalent

tion xe to a closure according to the abs rule Tocon

values

struct the environment of the closure wecho ose a typ e as

signment such that x e is derivable via

ve

the context rule and xe e In eect these rules

Sharing Environments

require that every binding in the closures environmentmust

Some implementations of languages

b e in scop e ieinfx g and the environmentisre

share p ortions of an environment among closures in an eort

quired to contain bindings for all of the free variables in

to decrease space and closure creation time In this section

the original function x eHowever mayalsocontain

we extend the treatment of abstract closure conversion to

bindings for variables that are in scop e but do not o ccur free

allo w for shared environments Weachieve this by imp os

in the function Consequently there are manychoices for

ing additional structure on environments to allow for nested

with the exact choice b eing inuenced by time and space

representations

considerations

The typ e assignments in the previous section consist

We construct the environment of a closure via the context

of a at sequence of variable declarations Toprovide for

rule by translating eachofthevariables o ccurring in

shared environment representations weenrich the structure

namely x x to the target expressions e e We

n n

of typ e assignments to supp ort nested typ e assignments as

place the resulting expressions in a tuple he e ito

n

follows

form the environment data structure of the closure This

fx gjh i

m

i representation of the environmenthastyp e h

n

whichwe summarize by writing j j

Anestedtyp e assignment is either a single typ e binding

To pro duce the co de of the closure we translate the b o dy

or a sequence of nested typ e assignments The environment

of the source function under the strengthened assumptions

corresp onding to the typ e assignment has target language

x pro ducing the b o dy of the co de e Wethenab

typ e jj where jfx gj and jh ij hj j

m

stract the environment and argument yielding the transla

j jiWe can obtain a nonnested typ e assignment

m

tion x j jx e

ve

from a nested typ e assignment simply by dropping

Using a dummy current argument to translate an en

the extra structure

tire closed program it is easy to proveby induction on the

We give the most imp ortant translation rules for closure

derivation of the translation that the translation preserves

conversion with nested environments in Figure the re

the typ e of a program

maining rules may b e obtained from those in Figure by

Theorem If e and xbe e then e

replacing with throughout

Weusetheenvtuple rule to construct a nested envi

To prove the correctness of the translation weuseatyp e

ronment he e i corresp onding to the typ e assignments

n

indexed family of logical relations relating closed source ex

ifx e for i nWe ob

n i i

pressions to closed target expressions and closed source

tain each of the and e from the arg envsubenv

i i

values to closed target values The relations are dened

and envtuple rules We use the arg rule to translate the

by induction on source typ es as follo ws

argument of the nearest enclosing abstraction as an en

e e i e v and e v and v v

vironment and weusetheenv rule to translate the free

c c

b

variables of this abstraction as an environment As b efore

vv v v v v i for all v v

  we use the distinguish ed variables x and x to hold these

ve

twovalues in the translation We use the subenvruleto

We extend the relation to nite source and target sub

translate access to a typ e assignment nested within to a

stitutions mapping variables to their resp ective class of

xfx g e

arg fx g xfx g x envx x var

ve

xx e

x e x e x e

n n i

envtuple subenv

h i x e x x xh i he e i

n i ve ve n n

Figure SimplyTyp ed Closure Conversion using Nested Environments

pro jection of the environment corresp onding to Finally Closure Representation

we translate access to a variable within a typ e assignment

The purp ose of abstract closure conversion is to cho ose an

via the var rule

environment representation for each closure and to make the

As an example consider the translation

construction of closures explicit By making environments

explicit we exp ose op erations that are implicit at the source

hfx intg fx intgi x int xintx x x

level to an optimizer at the target level In particular an

hhx xint x x x

ve ve ve ve

optimizer can eliminate redundant constructions of environ

hx x iii

ve

ments or redundant pro jections from environments

However the pro cess of extracting the co de and environ

where is hint hint intiiWe construct the new envi

ment of a closure remains an implicit atomic op eration of

ronment for the closure by pairing the current argument x

the op erational semantics Hence we cannot optimize these

and the currentenvironment x according to the envtuple

ve

closure op erations For instance if the same closure is re

rule If we used the at translation given in Figure then

p eatedly applied in a lo op it is not p ossible to extract the

wewould have to pro ject the values for x and x out of the

co de and environment once rep eating only the application

currentenvironment and place these values and the current

to the environment and argument within the lo op

argumentinto a newly allo cated tuple

To makesuch optimizations p ossible wecho ose a rep

Nested typ e assignments are suciently exible to han

resentation of closures in terms of generic primitives that

dle many commonlyused environment representations For

would in practice already b e present in the intermediate

example the Categorical Abstract Machine or CAM

language Sp ecicall ywe consider a target language

uses a linked list to represent the environment This is re

with existential typ es dened by the following grammar

ected in our framework by restricting the shap e of nested

typ e assignments and by restricting the envtupleruleto

ij Types b j t jh

n

cons the current argumentonto the currentenvironment

code jt

ve

as follows

Exps e c j e e e j x x e j

ve ve

CAM context fx gjhfx g i

c c

he e ij e j

n i

pack with e as j

envtuple xhx i hx x i

c c ve

open e as t with x in e

The advantage of the CAM strategy is that the cost of the

This language includes existential typ es and co de typ es

construction of a new environment is constant However

but not function typ es we showhow to dene function typ es

in the worst case accessing values in the environmenttakes

in terms of these primitive constructs We restrict applica

time prop ortional to the length of the environment

tions to the form e e e in order to preclude a partial

In contrast the FAM uses at environments with no

application of co de to its environment this can b e seen as

sharing The closure conversion of Figure accurately mo d

a sp ecialized use of m ultiargument functions

els the environment strategy of the FAM if wecho ose a sp e

Typing judgements for are of the form e

cic strengthening strategy in the abs rule where only the

where is a list of typ e variables in scop e and is a typ e

free variables of the function are preserved in the resulting

assignment for variables in scop e We assume that the free

closures environment The advantage of the FAM environ

typ e variables of the typ es in the range of and the free typ e

ment representation is that the cost of variable lo okup is

variables of e and are contained in The typing rules

always constant and the representation is safe for space

and evaluation rules of the language are standard see

according to App els denition However constructing

and Figure

the environment for a closure takes time prop ortional to the

We describ e the closure representation phase in two parts

numb er of free variables in the function and closures cannot

cl

We b egin by dening a translation from to typ es de

share p ortions of their environment

noted j j as follows

Clearly there are a variety of other strategies for form

ing environments For example the shared closure strat

jbj b

egy describ ed by App el and Shao that is also safe for

jh ij hj j j ji

n n

space can also b e formulated in our framew ork However

jcode j codej j j j j j

ve ve

to determine a go o d representation for each closures envi

j j t hcodet j j j j t i

ve ve ve

ronment requires a go o d deal more information including

an estimate as to howmany times eachvariable is accessed

We translate an arrowtyp e to a pair consisting of co de and

when garbage collection can o ccur what garbage collection

an environment with the environmenttyp e held abstract

algorithm is used etc

using an existential quantier

e code e e e

ve ve ve

ve

closure

i as j j hhe e ii pack j j with he e

ve ve

ve

e e e e

app e e x Dom

open e as t with xhcodet j j j j t i in x x e

ve ve ve

Figure Imp ortant Rules of SimplyTyp ed Closure Representation

cl

Next we dene the translation of terms to terms and value environments In addition wemust abstract b oth

in Figure The judgements of the translation are of the thekindofthetyp e environment and the typ e of the value

cl

form e e where e and are a typ e as environment so that their representations remain private to

signment expression and typ e resp ectively and e is a the closure Without the abstraction we run into the same

expression The interesting rules are closureandapp typing problems that we encountered in the simplytyp ed

cl

case

The other rules not shown simply map the other con

As a running example consider the expression

structs to their counterparts We translate a closure to a

pair of the co de and the environmentpacked with the typ e

xt xt y t zint

of the environment We translate an application to an open

extract from a package the pair of a co de and an environ

where t and t are free typ e variables and y and z are free

ment and then apply the co de to the environment and the

value variables of typ e t and int resp ectively Itiseasyto

argument

check that this expression has typ e t t t int To

closure convert the expression we translate it to the partial

It is easy prove that the translation preserves the typ e

application

of a program up to the translation of the typ e Wedoso

by rst extending the typ e translation to typ e assignments

let val code

setting

tenv ft t g

venv fyt tenv zintg

jfx x gj fx j j x j jg

n n n n

xt tenvx y venv z venv

Theorem If e and e e then jj

in

e j j

code ft t t t gfyy zzg

end

Correctness of the translation is proven using logical re

cl cl

lations b etween and expressions and values

The co de of the closure abstracts a typ e environment tenv

cl

and and substitutions The denition of the rela

andavalue environment venv The actual typ e environment

tions and the pro of of the correctness can b e found in our

ft t t t g is a record of ft t g where is the

technical rep ort

kind of monotyp es The actual value environment fyy

zzg is a record with typ e fyt zintg Note however

that this typ e contains a free reference to t whichmust

Overview of Polymorphic Closure Con

b e replaced by a reference to the typ e environment in order

version

to ensure that the translated co de is closed We therefore

ascrib e the typ e fyt tenv zintg to the value environ

Closure conversion for a language with MLstyle iepred

ment noting that the pro jection t tenv is equivalentto

icative explicit p olymorphism follows a similar pattern

t when the actual typ e environmentisasgiven earlier By

to the simplytyp ed case but with two additional compli

similar reasoning we assign the typ e t tenv to the argu

cations First wemust account for free t yp e variables as

ment x of the abstraction It is easy to check that the

well as free value variables in the co de of an abstraction

co de of the closure has the typ e given by the equation

co de

Second wemust create closures for b oth value abstractions

terms and typ e abstractions terms In this section

co de

we giveanoverview of the typing diculties encountered

tenvft t g

when closure converting value abstractions the treatment

fyt tenv zintg

of typ e abstractions is similar see Section for details

t tenvt tenvt tenvint

To eliminate free o ccurrences of typ e variables and or

It follows that the entire let expression has the typ e of the

dinary variables from the co de we abstract with resp ect

original term namely t t t int

to a typ e environmentandavalue environment replacing

free variables by references to the appropriate environment

Now let us consider the representation of the partial ap

This pro cess results in closed co de that can b e hoisted to

plication of code to its typ e and value environments as a

the top level and shared among multiple closures The co de

data structure This data structure must b e mixed phase

is partially applied to suitable representations of the typ e

in the sense that it consists of b oth typ e and value comp o

and value environments to form a p olymorphic closure As

nents This suggests using a package of existential typ e of

in the simplytyp ed case we need a data structure to repre

the form

sent the delayed partial application of the co de to its typ e

tenv ft t t t g e pack ft t t t g with code fyy zzg

te

yt tenvzintgt tenv f as t

te te co de ve

t tenvt tenvint

where code is as given earlier and

This typ e is a sup ertyp e of the original co de typ e

co de

ft t g

te

b ecause wehave constrained the b ound typ e variable tenv to

fyt t zintg

ve te

b e b ound to a particular typ e namely the typ e environment

of the closure See Harp er and Lillibrid ge and Leroy

This package is welltyp ed according to the usual rules for

for further discussion of subtyping in this setting This

existentials

constraint ensures that this reference to the co de will only

In contrast consider what happ ens when we attempt to

b e applied to the typ e environment of the closure

give the translation of the application of e to an argument

The constraintontenv allows us to conclude that t

e of typ e t Pro ceeding as in the simplytyp ed case wein

tenv is equivalenttot and similarlythatt tenv is equiv

tro duce an open expression that extracts the co de the typ e

alenttot We propagate these equivalences into the typ e

environment and the value environment from the closure

yielding

and applies the co de to the environments and argument

Doing so results in the following translation

tenv ft t t t g

te

f yt zintg t t t int

open e as t with w

te te co de ve

in

Wecannow form the package containing the typ e envi

w t w e

te

ronment co de and value

end

pack ft t t t g with code env

Unfortunately this expression is not welltyp ed The di

as t

te te ve

culty is that e has typ e t whereas the expression w

where is given via the equation

t w has typ e

te

tenvt fyt t zintg

te te te

t t t t t t int

te te te

t t t t t t int

te te te

Since t is abstract the typ e variable t is not equivalent

te

and sho wthatthispackage has typ e t Note

te te ve

to t t Consequently the prop osed translation of appli

te

that is the same as thetyp e of the partial application

c

cation fails to typ echeck

of code to the typ e environment except for the additional

One way to get around this problem is to apply the co de

constrained typ e abstraction of tenv Through the use of

to the typ e environment b efore forming the closure This

translucencywehave accomplished the eect of partial ap

yields

plication at the typ elevel without actually p erforming the

let val c code ft t t t g

application at the termlevel

in

Op ening a package e of typ e t to apply to

te te ve

pack ft t t t g with c fyyzzg

an argument e of typ e t yields

as t

te te c ve

open e as t w

te te ve

end

in

where the typ e is given by the equation

w t w e

c

te

end

fyt t zintgt t

c te te

t t t t int

t t The expression w t w e has typ e

te te

te

t int thus the entire expression is wellformed

The translation of application given ab ove will work in this

In summarywe use transluceny to constrain the typ e

case b ecause the co de and the value environment b oth use

of co de b efore placing it in a closure We use packtorep

t as the t yp e environment But this approachdepends

te

resent the mixedphase data structure containing the co de

up on the very mechanism we are attempting to eliminate

typ e environent and the value environment The resulting

namely partial application The partial application of the

package has a typ e of the form

co de to the typ e environment pro duces co de that is no longer

closed Thus the co de cannot b e shared among the dierent

t tt

te te te te ve ve

instantiation s of the typ e environment

Toavoid the typing problems encountered in the simply

Our solution to this issue is to constrain the co de so

typ ed case we need to hide the representations of the value

that it can b e applied to a closures value environmentonly

environment and the typ e environment Thus we use pack

when it is also applied to the same closures typ e environ

again to abstract the kind of the typ e environment and the

ment This ensures that the typ e environment passed to the

typ e of the value environment resulting in the following typ e

co de and the typ e environment used in the construction of

for closures

the closures value environment are the same Fortunately

typing constraints of this form have already b een addressed

k t t k tt k t t

te ve te te te te ve ve

by research on mo dule systems

Following Harp er and Lillibri dg e we use the notion

Careful consideration of the foregoing discussion reveals

of translucent typ es to express the desired constraintonthe

that we only made limited use of translucency The univer

co de In particular when forming the closure wecoercethe

sally quantied variable tenv do es not o ccur in the scop e

co de to have the translucenttyp e

of the abstraction once the equational constraintontenv is

propagated We use this prop ertytoprovide a substantially the domain of Typing judgements are derived according

simpler mechanism than the full translucenttyp e calculus to the standard typing rules of the secondorder calculus

In particular we only need to capture the restriction that see for example The most interesting rules are

a p olymorphic function must b e applied to a sp ecic typ e the intro duction and elimination rules for quantied typ es

argument This may b e expressed byintro ducing a typ e

ftg e

consisting of functions that must b e applied to the

t Dom

t e t

constructor to yield a value of typ e The following two

rules govern this new typ e constructor

e t

FTV Dom

e t

e e t

e t e

Abstract Closure Conversion

The rst rule restricts the domain of typ e applicatio n to the

Abstract closure conversion for converts b oth abstractions

sp ecic constructor This corresp onds to restricting the

and abstractions into abstract closures consisting of co de

typ e to t and propagating the equivalence t into

atyp e environmentandavalue environment We consider

The actual typ e application for is p ermitted only

here only at environment representations but note that the

for constructors equivalentto These two rules naturally

treatment of nested environments given in Section carries

come from the necessity of delaying typ e application s for

over to the p olymorphic case

closure conversion Using this notation the typ e translation

cl

We dene the syntax of the target language as fol

of b ecomes

lows

k t t k t t t

Kinds jh i

te ve te te te ve ve

Cons b j t j jh ij

n

The typ e of closures abstracts the kind of the typ e en

h ij j

n i

vironment and the typ e of the value environment ensuring

Types j jt jh ij

n

h closure in the that these maybechosen separately for eac

vcodet j

te te ve

system As in the simplytyp ed case wehave obtained an

tcodet t

te te ve

ob ject oriented representation of p olymorphic closures by

Exps e c j x j e e j e jhe e ij e j

n i

exploiting a combination of the typ e systems prop osed by

j t x x e

te te ve ve

Pierce and Turner for ob jects and by Harp er and Lil

t x te jhhe e ii

te te ve ve

libridge for mo dules

We use pro duct kinds of the form h i to sp ec

n

ify the shap es of typ e environments in much the same way

AFormal AccountofPolymorphic Clo

that we use pro duct typ es to sp ecify the shap es of value

environments

sure Conversion

There are two sorts of co de co de corresp onding to an or

dinary abstraction has the form t x x e

In this section wepresent closure conversion for the predica te te ve ve

while co de corresp onding to a typ e abstraction has the form

tive fragment of the second order calculus This fragment

t x te The co de in each case abstracts

is sucient to mo del Standard ML and admits rela te te ve ve

atyp e en vironmentandavalue environment For the

tively simple correctness pro ofs based on logical relations

case the co de also abstracts a value argument and for the

Our results extend to the full impredicative p olymorphic

case the co de abstracts a typ e argument Weintro duce

calculus but at the exp ense of a substantiall y more complex

the typ es vcode and tcode to distinguish the twotyp es of

correctness argument based on Girards metho d of candi

co de from the typ es of closures to ensure closure conditions

dates

on co de and to preclude partial application s of co de to en

We dene the syntax of the source language as follows

vironments These typ es may b e describ ed by the following

Kinds

informal corresp ondences

Constructors b j t j

vcodet t

te te ve te te ve

Types j jt

tcodet t t t

te te ve te te ve

Expressions e c j x j x e j te j e e j e

Values v c j x e j te

We consider co de typ es to b e p olymorphic so these typ es

do not lie in the range of a p olymorphic quantier

We use kinds to describ e constructors andtyp es

Abstract closures have the form hhe e ii consisting of

to describ e expressions e There is only one kind

piece of co de e atyp e environment andavalue environ

cl

for but since subsequent languages havearicher kind

ment e

cl

structure weintro duce kinds here for uniformity Closed

For the typing of kind assignments map typ e

constructors of kind corresp ond to a subset of typ es in

variables to kinds while typ e assignments map value

particular the typ es that do not include quantiers the

variables to typ es The judgements of the static semantics

monotyp es Thus constructors of kind can b e injected

are as follows

into typ es We leave this injection implicit and treat as

is a wellformed constructor of kind

b oth a constructor and a typ e

is a wellformed typ e

A kind assignment is a sequence that maps typ e vari

and are equivalent constructors

ables to kinds and is of the form ft t gn

n n

and are equivalenttyp es

Typing judgements are of the form e where the

e e is a wellformed expression of typ e

free typ e variables of eand are contained in the do

This restriction is relaxed in the impredicative case main of and the free value variables of e are contained in

The formation rules of typ es are standard Wehavetoin Theorem If e e and

env arg env arg env

tro duce denitional equality of constructors and typ es to e then ft j jg fx j jg

arg env arg te env arg ve

env

e where account for pro jections of constructors from pro duct kinds

env arg env arg

arg

and These rules consist of the equivalence rules for pro jections

env arg arg env

arg env

b elow as well as the standard rules for equivalence and con

The correctness of the translation may b e established us

gruence

ing an argument similar to that given for the simplytyp ed

case The restriction to predicative p olymorphis m signi

h i

i n i i

cantly simplies the pro of

h i h i

n n

The typing rules for expressions are standard except for

Closure Representation

the rules for co des and closures These rules are dened in

Figure We require that co de values b e closed with resp ect

Wenow turn to the representation of closures for the p oly

to b oth typ e variables as well as value variables This allows

morphic language

us to share the co de among multiple instantiatio ns of the free

The target language for p olymorphic closure representa

typ e variables and free value variables

tion called is dened as follows

cl

We dene abstract closure conversion from to by

Kinds k j jh i

n

the deductive system given in Figures and The judge

j Types b j t jh ijh ij

i n n

ment means that is the translation of

env arg

t j j jt jk

where is a kind assignment corresp onding to a typ e

env

Exps e x j c j xe j e e j te j ej

environment and is a kind assignment corresp onding

arg

he e ij e j

n i

to a typ e argumentifany This judgement also implic

pack with e as j

itly denes a translation from constructors to constructors

open e as t with x in e

since sourcelevel constructors are a subset of typ es

pack with e as j

and the translation maps constructors to constructors In

open e as k with x in e

translated programs the typ e variable t is used for typ e

te

environments

Our translation of function typ es inv olves existential quan

The judgement e e means

env arg env arg

tiers Since function typ es can instantiate a p olymorphic

e is a translation of e where and are as in the

env arg

typ e in the source language we need to b e able to instantiate

typ e translation and and are typ e assignments

env arg

p olymorphic typ es with existentials in the target language

corresp onding to the value environment and value argument

As a consequence the target language must b e impredica

resp ectivelyAtyp e environment corresp onding to and

env

tiveTo simplify the language weprovide general abstrac

avalue environment corresp onding to are implemented

env

tions and instead of co de typ es that abstract more

in the target language bytyp es of the form j j and j j

en v env

than one argument at a time

resp ectively as dened b elow

Since we shall have limited need of existential kinds we

must intro duce kind variables k into the language with cor

jft t gj h i

n n n

resp onding kind contexts and judgements A kind context K

jfx x gj h i

n n n

is simply a sequence of kind variables fk k gn

n

The typing judgements of the language are as follows

The most interesting rules are the term translations of

value and typ e abstractions In each case an appropri

K has kind

ate typ e environment and value environmentmust b e con

K and are equal typ es of kind

structed as part of the closure Thus assignments and

env

K e e has t yp e

must b e chosen as subsets of the current assignments

env

and resp ectiv ely These assignments

env arg env arg

The formation rules denitional equality rules and typ

must b e chosen so that all of the free value variables of the

ing rules are standard except that values of p olymorphic

term are contained in and furthermore all of the free

env

typ e t maybecoercedtothespecialtyp e t

typ e variables of the term and the value environmentmust

where is a typ e of kind as describ ed in the Section

b e contained in

env

The details of the typing rules are found in the companion

The chief technical diculty in formulating these rules

technical rep ort

is that weneed two typ e assignments and tode

env env

We dene the closure representation stage as a typ e

scrib e the value environment of the closure dep ending up on

cl

directed translation from to We b egin by dening

the context The typ e assignment is constructed from

env

a translation from source constructors and typ es to target

the context and is used to build the

env arg env arg

typ e as follows

environment e in the context in which the closure is con

ve

structed The typ e assignment is obtained from

env env

jtj t

via the translation and corresp onds

env env env

jbj b

to the typ e of the value environment in the context of the

jh ij hj jj ji

n n

closure itself This ensures that the co de of the closure is

j j j j

i i

closed since the typ e ascrib ed to the value environment ar

jh ij hj j j ji

n n

gument do es not refer to free typ e variables in the context

jvcodet j tj jj j j j

ve ve

where the closure was created

jtcodet s j tj js j j

ve ve

The typ e correctness of the translation is proved byin

t j j j j t i j j kt tkht

duction on the derivation of the translation

js j kt tkht t sj j t i

ft g fx x ge

te te ve ve

t x x e vcodet

te te ve ve te te ve

ft tg fx ge

te te ve ve

t x te tcodet t

te te ve ve te te ve

e vcodet e t

te te ve te ve te

hhe e ii t

te

e tcodet t e t

te te ve te ve te

hhe e ii t t

te

cl

Figure Typing Rules for Co de and Closures of

b b ft t g t t

env arg n arg i i te

t t t Dom

env arg arg

ftg

env arg env arg env arg

t t

env arg env arg

t t

env arg env arg n

n

ft t g h i

env arg n

n

env arg env arg n

n

fx x g fx x g

env arg n n n

n

Figure Polymorphic Abstract Closure Conversion Typ es and Typ e Assignments

const c c

env arg env arg

env fx x g x x

env arg n n arg i i ve

arg x x x Dom

env arg env arg arg

e

te env arg env arg env arg env arg ve

env env

env env env env

abs

fx g e e

env env

e e ii jx jx j x e hht j

te ve ve env arg env arg te

env env

e

ve te env arg env arg env arg env arg

env env

ftg e e

tabs

env env env env env

te hht j jx j jte e ii

env arg env arg te ve te ve

env env

e e e e

env arg env arg env arg env arg

app

e e e e

env arg env arg

e e

env arg env arg env arg

tapp

e e

env arg env arg

x e

env arg env arg i

i

context

fx x g he e i

env arg env arg n n

n

Figure Polymorphic Abstract Closure Conversion Terms

compiler Indeed automatic typ echecking has enabled us The co de typ es are translated to the appropriate combi

to isolate and eliminate various subtle bugs in TIL nation of target and typ es The translation of a function

For simplicity the current implementations of our com typ e abstracts the kind of the typ e environment k and the

pilers use only abstract closure conversion However b oth typ e of the value environment t The typ e environment t

compilers extend this translation to avoid creation of clo is paired with the co de by using an existential typ e Since

sures for known functions in the style of Wand and Steck the typ e of a co de is instantiated by t only the typ e envi

ler In the future we hop e to use the closure representa ronment of the closure can b e given to the co de The co de

tion phase describ ed here to further exp ose closure handling and the value environment are paired as in the simplytyp ed

op erations to optimization case The translation of has the same structure as that of

an arrowtyp e

The translation of expressions is summarized in Figure

Acknowledgements

The kind of the typ e environment the typ e of the value en

vironment and the typ e environment are packed with the

Wewould like to thank Lars Birkedal Andrzej Filinski

pair of the co de and the value environment In the transla

Mark Leone Sue Older Benjamin Pierce Paul Steckler

tion of application s the typ e environment is obtained from

David Tarditi and the anonymous reviewers for their many

a closure byanopen expression and the co de and the value

helpful comments and suggestions

environment are obtained by pro jections Then the typ e

environment the value environment and the argumentof

application are passed to the co de

References

Typ e preservation is proved by induction on the struc

A W App el Compiling with Continuations Cambridge

ture of the translation derivation The typing rules for

University Press

are essential to prove the cases for the translations

A W App el and T Jim Continuationpassing closure

of closures

passing style In ACM Symp on Principles of Programming

Theorem If e e then jj e j j

Languages

D E Britton Heap storage management for the program

The correctness of the translation can b e proven using

ming language Pascal Masters thesis University of Arizona

logical relations as in the simply typ ed case However the

denition of the relations is more complicated b ecause of the

L Cardelli The functional abstract machine Polymorphism

presence of p olymorphic typ es and typ es of the form

i

cl

in the language The relations and the pro of app ear

C Cousineau PL Curien and M Mauny The categorical

in the companion technical rep ort

abstract machine In Functional Programming Languages

and Computer Architecture pages

Summary and Conclusions

H Friedman Equalitybetween functionals In R Parikh

editor Logic Col loquium NorhHolland

Wehave given a typ etheoretic account of closure conversion

es JY Girard Y Lafont and PTaylor Proofs and Typ

by dening typ edirected transformations for the simply

volume of Cambridge Tracts in Theoretical Computer Sci

typ ed and p olymorphic calculi The typ es used in the

ence Cambridge University Press Cambridge England

target languages of the translations maybecharacterized

in a natural way based on the closures as ob jects prin

J Gosling Javaintermediatebyteco des In ACM SIG

ciple In b oth the simplytyp ed and p olymorphic cases of

PLAN Workshop on Intermediate Representations IR

closure representation we used PierceTurnerstyle existen

Jan

tials to hide the representations of environments In the

J Hannan A typ e system for closure conversion In The

tage of Harp erLillibri dg e p olymorphic case wetookadvan

Workshop on Types for Program Analysis

style translucency to ensure that the same typ e environment

R Harp er and M Lillibridge Explicit p olymorphism and

is used to typ e b oth the co de and the value environmentof

CPS conversion In ACM Symp on Principles of Program

a closure

ming Languages

Our translations preservetyp es facilitating correctness

pro ofs and comp osition with other typ ebased translations

R Harp er and M Lillibridge A typ etheoretic approach

to higherorder mo dules In ACM Symp on Principles of

Furthermore our translations provide supp ort for runtime

Programming Languages pages

typ e analysis and typ ebased tagfree garbage collection

Wehave put the ideas in this pap er to practical use in

R Harp er D MacQueen and R Milner Standard

two separate compilers for ML One compiler is b eing used

ML Technical Rep ort ECSLFCS Lab oratory for

the Foundations of Computer Science Edinburgh University

to study novel approaches to tagfree garbage collection

Mar

The other compiler called TIL Typ ed Intermediate Lan

guages provides a general framework for analyzing typ es

R Harp er and J C Mitchell On the typ e structure of Stan

at run time to supp ort ecient data representations e

dard ML ACM Transaction on Programming Languages

and Systems

cient calling conventions and nearly tagfree garbage col

lection in the presence of p olymorphism Propagating

R Harp er and G Morrisett Compiling p olymorphism using

typ es through closure conversion is necessary for b oth com

intensional typ e analysis In ACM Symp on Principles of

pilers so that typ es can b e examined at run time

Programming Languages pages

Wehave found that propagating typ es through closure

T Johnsson Lamb da lifting Transforming programs to re

conversion and other compilation phases has an additional

cursive equations In Functional Programming Language and

engineering b enet In particular we can automatically ver

Computer Architecture LNCS pages Springer

ify the typ eintegrityofeachtyp epreserving phase in the Verlag

e vcodet e e e

te te ve ve

ve ve

vcl

i as j j hhe e ii pack j j j j with he e

ve te ve

ve

e e e e

e e open e as k t t

te ve te

app

with y ht t j jj jt i

te ve ve

in y t y e

te

e tcodet t e e e

te te ve ve

ve ve

tcl

i as jt j hhe e ii t pack j j j j with he e

ve te ve

ve

e t e

e t open e as k t t

te ve te

tapp

with y ht t tj jt i

te ve ve

in y t y j j

te

Figure Polymorphic Closure Representation

R Kelsey and P Hudak Realistic compilation by program Z Shao and A W App el Spaceecient closure represen

translation detailed summary In ACM Symp on Prin tations In Proc ACM Conf Lisp and Functional Program

ciples of Programming Languages pages ming

D Kranz et al Orbit An optimizing compiler for Scheme

Z Shao and A W App el A typ ebased compiler for Stan

In Proc of the SIGPLAN Symp on Compiler Construc

dard ML In Programming Language Design and Its imple

tion

menation pages

X LeroyUnboxed ob jects and p olymorphic typing In ACM

R Statman Completeness invariance and lambda

Symp on Principles of Programming Languages

denability Journal of Symbolic Logic

X Leroy Manifest typ es mo dules and separate compila

R Statman Logical relations and the typ ed calculus In

tion In ACM Symp on Principles of Programming Lan

formation and Control

guages pages

G L Steele Jr Rabbit A compiler for Scheme Masters

D MacQueen Mo dules for Standard ML In Proc ACM

thesis MIT

Conf Lisp and Functional Programming pages

W W Tait Intensional interpretation of functionals of nite

Revised version app ears in

typ e Journal of Symbolic Logic

Y Minamide G Morrisett and R Harp er Typ ed closure

conversion Technical Rep ort CMUCS Scho ol of

D Tarditi G Morrisett P Cheng C Stone R Harp er

Computer Science Carnegie Mellon University July

and P Lee TIL A typ edirected optimizing compiler for

ML Technical rep ort Scho ol of Computer Science Carnegie

J C Mitchell and G D Plotkin Abstract typ es haveexis

Mellon University Oct To app ear

tential typ e ACM Transaction on Programming Languages

and Systems

A Tolmach Tagfree garbage collection using explicit typ e

parameters In Proc ACM Conf Lisp and Functional Pro

G Morrisett M Felleisen and R Harp er Abstract mo dels

gramming pages June

of memory management In Functional Programming Lan

guages and Computer Architecture pages June

R W ahb e S Lucco T Anderson and S Graham Ecient

R Morrison A Dearle R Connor and A L Brown An softwarebased fault isolation In th ACM Symposium on

ad ho c approach to the implementation of p olymorphism Operating Systems Principles Dec

ACM Transaction on Programming Languages and Systems

M Wand and P Steckler Selective and lightweight closure

conversion In ACM Symp on Principles of Programming

A Ohori A compilation metho d for MLstyle p olymorphic

Languages

record calculi In ACM Symp on Principles of Programming

Languages

B C Pierce and D N Turner Simple typ etheoretic foun

dations for ob jectoriented programming Journal of Func

tional Programming Apr A preliminary

version app eared in Principles of Programming Languages

and as University of Edinburgh technical rep ort ECS

LFCS under the title Ob jectOriented Program

ming Without RecursiveTyp es

G D Plotkin Lamb dadenability in the full typ e hierarchy

In To HBCurry Essays on Combinatory Logic Lambda

Calculus and Formalism Academic Press

U S Reddy Ob jects as closures In Proc ACM Conf Lisp

and Functional Programming

J C Reynolds Denitional interpreters for higherorder

programming languages In Pro ceedings of the Annual ACM

Conference pages