Massachusetts Institute of Technology

Artificial Intelligence Laboratory

AI Memo March

DRAFT

Ob jectOriented Programming in Scheme

Norman Adams

Jonathan Rees

Abstract

We describ e a small set of additions to Scheme to supp ort ob ject

oriented programming including a form of The

extensions prop osed are in keeping with the spirit of the Scheme lan

guage and consequently dier from Lispbased ob ject systems such as

Flavors and the Common Lisp Ob ject System Our extensions mesh

neatly with the underlying Scheme system We motivate our design

with examples and then describ e implementation techniques that yield

eciency comparable to dynamic ob jectoriented language implemen

tations considered to b e high p erformance The complete design has an

almostp ortable implementation and the core of this design comprises

the ob ject system used in a dialect of Scheme The applicative bias

of our approach is unusual in ob jectoriented programming systems

This rep ort describ es research done at the Articial Intelligence Lab oratory of the

Massachusetts Institute of Technology Supp ort for the lab oratorys articial intelli

gence research is provided in part by the Advanced Research Pro jects Agency of the

Department of Defense under Oce of Naval Research contracts NK

and NK

This is a revision of a pap er that app eared in the Proceedings of the ACM

Conference on Lisp and

c

Asso ciation for Computing Machinery

Introduction and terminology

Scheme is nearly an ob jectoriented language This should come as no

surprise since Scheme was originally inspired by Actors Hewitts message

passing mo del of computation Steele has describ ed the relationship

b etween Scheme and Actors at length We take advantage of this rela

tionshipand we try not to duplicate functionality that Scheme already

providesto add full supp ort for ob jectoriented programming Our exten

sions are in keeping with the spirit of Scheme It was designed to have

an exceptionally clear and simple semantics and few dierent ways to form

expressions

We develop examples of how one might program in Scheme using ob ject

oriented style Inherited b ehavior is handled in a straightforward manner

We show that a new disjoint data type for instances must b e added to Scheme

in order to p ermit application of generic op erations to all Scheme ob jects

and that making generic op erations anonymous supp orts mo dularity We

complete our presentation by showing how to obtain go o d p erformance for

generic op eration invocation

We use the terms object and instance idiosyncratically an ob ject is

any Scheme value an instance is a value returned by a constructor in the

ob ject system An operation sometimes called a generic function can b e

thought of as a pro cedure whose denition is distributed among the various

ob jects that it op erates on The distributed pieces of the denition are called

metho ds

Ob jectoriented programming using pro cedures

Simple ob jects

Our rst approximation to ob jectoriented programming in Scheme is straight

forward an instance is represented as a pro cedure that maps op erations to

metho ds A metho d is represented as a pro cedure that takes the arguments

to the op eration and p erforms the op eration on the instance

As an example consider the following denition of a constructor for cells

define makesimplecell value

lambda selector

cond eq selector fetch

lambda value

eq selector store

lambda newvalue

set value newvalue

eq selector cell

lambda t

else nothandled

define acell makesimplecell

acell fetch !

acell store ! unsp ecied

acell cell ! true

acell foo ! error

Each call to makesimplecell returns a new cell Abstract op erations

are represented by symbols here fetch store and cell An instance

is represented by the pro cedure returned by the constructor The lexical

variables referenced by the metho ds serve the purp ose of instance variables

To p erform an op eration on an instance the instance is called passing the

op eration as the argument the resulting metho d is then applied to the

arguments of the op eration There is no explicit notion of class but the

co de p ortion of the closure constructed for the expression

lambda selector

serves a similar purp ose it is static information shared by all instances

returned by the makesimplecell constructor

An instance returns the ob ject nothandled instead of a metho d to

indicate it denes no b ehavior for the op eration The particular value of

nothandled is immaterial as long as it is identiable as b eing something

other than a metho d We will make use of this prop erty later

define nothandled list nothandled

To improve the readability of op eration invocation we introduce the

pro cedure operate

define operate selector theinstance args

apply theinstance selector args

This lets us replace acell store with the somewhat more

p erspicuous

operate store acell

Operate is analogous to send in old Flavors and in CommonOb

jects

Inheritance

The following denes a named cell that inherits b ehavior from a simple

cell

define makenamedcell

lambda value thename

let scell makesimplecell value

lambda selector

cond eq selector name

lambda thename

else scell selector

We say that ob jects returned by makenamedcell have two components

the expression makesimplecell yields the rst comp onent and

the expression lambda selector yields the second The program

mer controls what state is shared by choosing the arguments passed to the

constructors and by choosing the expressions used to create the comp onents

In this style of inheritance only b ehavior is inherited An instance can name

its comp onents but can assume nothing ab out how they are implemented

We have single inheritance if the instance consults one comp onent not

including itself for b ehavior We have multiple inheritance if the instance

consults multiple comp onents not including itself for b ehavior For the

ab ove example that might b e done by expanding the else clause as follows

else let method scell selector

cond eq method nothandled

anothercomponent selector

else method

This is similar to the style of inheritance in CommonObjects in that in

stance variables are considered private to the comp onent and cannot b e in

herited However CommonObjects forces the comp onents to b e new where

our formulation has no such requirement thus distinct instances may share

comp onents and in turn the comp onents state Because classes are not

explicit and it is p ossible to share state and b ehavior one may say this

approach provides delegation rather than inheritance When more

than one comp onent denes b ehavior for an op eration the b ehavior from the

more sp ecic comp onent the one consulted rst shadows the less sp ecic

Op erations on self

One frequently wants to write a metho d that p erforms further op erations on

the instance For example if we were implementing an op en output le as

an instance that supp orted writechar we could implement a writeline

op eration as a lo op p erforming writechar op erations on the instance itself

In simple cases a metho d can refer to the instance by using letrec in the

instances implementation

letrec self

lambda selector

cond eq selector writeline

lambda self string

operate writechar self char

self

When inheritance is involved this will not work The variable self will

not b e in scop e in the co de for inherited metho ds A comp onent that uses

letrec as ab ove will b e able to name its comp onent self but not the

comp osite A small change to the proto col for invoking metho ds remedies

this the comp osite is passed as an argument to every metho d

define operate selector theinstance args

apply theinstance selector theinstance args

Op erations on comp onents

Because comp onents may b e given names a comp osites metho d for a given

op eration can b e dened in terms of the b ehavior of one of its comp onents

For example we can dene a kind of cell that ignores stores of values that

do not satisfy a given predicate

define makefilteredcell

lambda value filter

let scell makesimplecell value

lambda selector

cond eq selector store

lambda self newvalue

if filter newvalue

operate store scell newvalue

else scell selector

This practice is analogous to sending to super in and callnextmethod

in the Common Lisp Ob ject System CLOS

There is a problem here When the comp osite p erforms an op eration on

a comp onent the self argument to the comp onents metho d will b e the

comp onent not the comp osite While this is sometimes useful we also need

some way to p erform an op eration on a comp onent passing the comp osite

as the self argument This is the customary op eration of send to sup er

and its analogues We can do this using a variant on operate that takes

as arguments b oth the comp osite and the comp onent from which a metho d

is to b e obtained

define operateas component selector composite args

apply component selector composite args

define operate selector instance args

apply operateas instance selector instance args

Integration with the rest of the language

Op erations on noninstances

One often wants to include noninstances in the domain of an abstract op era

tion For example the op eration print when p erformed on a noninstance

should invoke a printer appropriate to that ob jects type Similarly the

abstract op eration cell should apply to any ob ject in the Scheme system

returning false if the ob ject is not a cell But given our present denition

of operate we cannot meaningfully say operate op x unless x is an in

stance

We can make print work on noninstances if we can asso ciate metho ds

with every noninstance on which we exp ect to p erform op erations This is

accomplished with a simple change to operateas remember that operate

is dened in terms of operateas

define operateas component selector theobject args

apply getmethod component selector

theobject args

define getmethod component selector

if instance component

component selector

getnoninstancemethod component selector

We will consider the denition of instance b elow As for getnoninstance

method we would like it to b ehave in a manner consistent with the dispatch

routines we have set up for instances which are sp ecic to the particular

kind of ob ject b eing op erated on

define getnoninstancemethod object selector

cond pair object

getmethodforpair

symbol object

getmethodforsymbol

other types

object selector

define getmethodforpair pair selector

cond eq selector print

lambda self port

other metho ds

define getmethodforsymbol symbol selector

Unfortunately any time we want a new op eration to work on some kind

of noninstance we have to mo dify the appropriate noninstance dispatch

routine to handle the new op eration This presents problems b ecause these

dispatch routines are global resources for which there may b e contention

What if two dierent mo dules chose to dene incompatible b ehavior for a

shared op eration But even worse in the case of the cell op eration we

would have to mo dify al l dispatch co de even that for noninstances That

would hardly b e mo dular

One way to dene a default b ehavior for cell would b e to have a

vanilla ob ject analogous to class object in many ob ject systems that

acted as a comp onent of every ob ject instance or noninstance We could

change the dispatch for that comp onent every time we wanted to add a new

op eration to the system This approach would also suer the contention

problem mentioned ab ove

Instead of using such a vanilla ob ject we take the approach of asso

ciating default b ehavior with each op eration The default b ehavior is used

when there is no metho d for the op eration in the ob ject b eing op erated on

We change the denition of operateas to implement this

define operateas component selector composite args

let method getmethod component selector

if eq method nothandled

apply defaultbehavior selector composite args

apply method composite args

The pro cedures defaultbehavior and setdefaultbehavior main

tain a table mapping selectors to pro cedures that implement the default

b ehavior

setdefaultbehavior cell lambda f

define acell makesimplecell

operate cell acell ! true

operate cell ! false

Later we will see how to asso ciate default b ehavior with op erations without

using side eects

Returning to the predicate instance Our new version of operateas

indirectly uses instance to determine whether the ob ject is an instance

Dening instance to b e the same as procedure almost works but it fails

to account for the distinction b etween those pro cedures that ob ey the pro

to cols of the ob ject system and those that dont operate cell list

would generate an error instead of returning false

To implement instance we need to b e able to mark some pro cedures

as b eing instances But in Scheme the only op erations on pro cedures are

application and identity comparison eq So we must add a new primitive

type to Scheme disjoint from the types already provided that satises the

following rules

instanceref makeinstance x ! x

instance makeinstance x ! true

instance y ! false if y was not a value

returned by makeinstance

Instance constructors such as makecell must now mark instances using

makeinstance and getmethod must co erce instances to pro cedures using

instanceref

define getmethod component selector

if instance component

instanceref component selector

getnoninstancemethod component selector

define makesimplecell value

makeinstance lambda selector

Nonop erations applied to instances

In purely ob jectoriented languages all op erations are generic In our frame

work this would mean that a pro cedure call such as car x would b e inter

preted the same way as say operate car x Thus the domain of car

and other primitives would b e extended to include all instances that choose

to handle the corresp onding generic op eration

We consider this kind of extension to b e undesirable for a number of

reasons all of which stem from the fact that programs b ecome harder to

reason ab out when all op erations are generic For example if a call to car

can invoke an arbitrary metho d then a cannot assume that the

call will not have side eects If arithmetic can b e extended to work on

arbitrary ob jects then algebraic prop erties such as asso ciativity no longer

hold Not only is eciency impaired but programs can b ecome harder for

humans to understand as well

In the case of some system pro cedures however extension to instances

can b e very useful for the sake of mo dularity For example pro cedures on

IO p orts can probably b e extended without signicant impact on p erfor

mance and they may already b e generic internally to the system If such

pro cedures are extended the contract of the corresp onding abstract op er

ation must b e made clear to those programmers who dene metho ds for

them

One particular Scheme primitive can b e usefully extended to instances

without sacricing eciency or static prop erties pro cedure call This is

b ecause pro cedure call has no algebraic or other prop erties that are in danger

of b eing destroyed invoking a pro cedure can p otentially do anything at all

So we can arrange for the Scheme implementation to treat a combination

proc arg

the same as

operate call proc arg

whenever the ob ject proc turns out to b e an instance The call op eration

should also b e invoked whenever an instance is called indirectly via apply

or any other system pro cedure that takes a pro cedure argument

If in addition we dene the call op eration so that when applied to a pro

cedure it p erforms an ordinary pro cedure call then any lambdaexpression

lambda var body

is indistinguishable from the instance construction assuming alphaconversion

to avoid name conicts

makeinstance

lambda selector

cond eq selector call

lambda self var body

else nothandled

This means that if we take instance construction to b e primitive in our

language then lambda need not b e

Allowing the creation of instances that handle pro cedure call is equiva

lent to allowing the creation of pro cedures that handle generic op erations

Pro cedures that handle op erations can b e very useful in a language like

Scheme in which pro cedures have high currency In T for example the

op eration setter when applied to a pro cedure that accesses a lo cation

returns by convention a pro cedure that will store into that lo cation

operate setter car pair newvalue

is equivalent to

setcar pair newvalue

Car and other builtin access pro cedures are set up as if dened by

define car

makeinstance

lambda selector

cond eq selector call

lambda self pair

primitivecar pair

eq selector setter

lambda self setcar

else nothandled

T has a generalized set sp ecial form analogous to Common Lisps setf

that provides the more familiar syntax

set car pair obj

To dene a new pro cedure that works with set it is sucient to create an

instance that handles the call and setter op erations appropriately

The T system itself makes heavy use of op erations on pro cedures The

system printer and the trace facility provide two examples Often a pro

cedure has a print metho d that displays values of closedover variables so

that the pro cedure is easily identiable during debugging The trace util

ity creates a traced version of a given pro cedure the original pro cedure is

recovered by invoking an op eration on the traced pro cedure

Anonymous op erations

In our development so far as in Smalltalk and CommonOb jects sym

b ols are used to represent abstract op erations This practice can lead to

name clashes If two mo dules use the same symbol to represent two dier

ent abstract op erations then one mo dule may not work in the presence of the

other For example the two mo dules may require dierent default b ehav

iors for two dierent abstract op erations for which they have coincidentally

chosen the same name Or if mo dule A denes ob jects that include as com

p onents ob jects created by mo dule B ie sub classes one of Bs classes

then A might inadvertently use the name of an op eration intended to b e

internal to B When a metho d in B p erforms this op eration on instances

created by A the metho d in A will b e seen instead of the intended metho d

in B

The problem can b e eliminated if op erations are represented by unique

tokens instead of symbols New tokens must b e obtained by calling a sys

tem pro cedure that generates them The creator of the token can use lexical

scoping to control what other co de in the system may p erform the corre

sp onding abstract op eration In contrast to Common Lisp Scheme uses

lexical scoping to control visibility of names b etween mo dules We call this

feature anonymous operations b ecause although the token representing an

op eration is usually the value of some variable the name of the variable is

immaterial

Here is the cell example reformulated using anonymous op erations New

op erations are created with makeoperation which takes as an argument

the op erations default b ehavior

define fetch makeoperation error

define store makeoperation error

define cell

makeoperation lambda f

define makesimplecell

lambda value

makeinstance

lambda selector

cond eq selector fetch

lambda self value

eq selector store

lambda self newvalue

set value newvalue

eq selector cell

lambda self t

else nothandled

define acell makesimplecell

operate fetch acell !

The variables fetch store and cell are evaluated in the course of

dispatching and the selector argument in calls to operate is an op eration

not a symbol

How are we to represent op erations The only prop erty we need is that

they b e distinct from each other as determined by eq We could use

symbols generated by gensym or pairs but a b etter choice is to represent

op erations as pro cedures This way we can arrange that when an op eration

1

is called it p erforms itself on its rst argument

1

The denition of makeoperation given here requires every evaluation of the inner

lambdaexpression to result in a distinct closure However some Scheme may

try to optimize the storage allo cation p erformed by makeoperation by reusing the

same pro cedure ob ject every time This is not a serious diculty however since it is

always p ossible to circumvent such optimization s

define makeoperation defaultbehavior

letrec thisop

lambda theobject args

apply operate thisop theobject args

setdefaultbehavior thisop defaultbehavior

thisop

We can now convert from the message passing style interface that we

have b een using to a generic pro cedure style interface That is rather than

writing

operate fetch acell

we write

fetch acell

The advantages of the generic pro cedure style are describ ed in

If we are allowed to dene call metho ds on instances as describ ed in

section then we can eliminate the global table maintained by set

defaultbehavior and access an op erations default metho d via an op er

ation applied to the op eration itself

define makeoperation adefaultbehavior

letrec thisop

makeinstance

lambda selector

cond eq selector call

lambda self theobject args

apply operate thisop theobject args

eq selector defaultbehavior

adefaultbehavior

thisop

define defaultbehavior makeoperation error

Ecient implementation

We discuss two eciency problems dispatch time and metho d invocation

time We revise our formulation to cop e with the rst explain how a Scheme

compiler can help with the second and then consider the rst again but

with resp ect to comp osite ob jects

Reducing dispatch time

Dispatch time is the time sp ent mapping from op eration to metho d If there

are many op erations in a comp onent or many comp onents in a comp osite

then p erforming op erations will b e much slower than pro cedure call

Dispatch time in the examples presented is prop ortional to the number

of op erations handled Even if each comp onent p erforms its dispatch in

constant time say using a hash table dispatch time would still b e prop or

tional to the total number of comp onents from which the comp osite ob ject

inherits Two problems with p erforming hashes in comp onents arise

 If the number of op erations p er comp onent tends to b e small hash

lo okup may b e slower than linear search Hashing may b e practical in

comp osite ob jects if we can combine the dispatches of all the comp o

nents A way to do this is describ ed b elow

 A naive approach would result in a distinct hash table p er instance

This is far to o costly in space Having like instances use the same hash

table is problematic for two reasons

{ A shared table cannot map from op erations to metho ds b ecause

the metho ds vary from instance to instance This is b ecause we

have chosen to represent metho ds as closures that include the

environment sp ecic to the instance

{ In the example ab ove the anonymous op erations were b ound to

global variables this need not b e so If the op erations are lo

cally b ound the keys for the table may change from instance to

instance

To x these problems we separate op eration dispatch from metho d in

vocation makeinstance now takes two arguments a dispatcher and a

metho d invoker We then have

instance makeinstance d i ! true

instancedispatcher makeinstance d i ! d

instanceinvoker makeinstance d i ! i

instance y ! false if y was not a value

returned by makeinstance

A dispatcher maps an op eration to a method index The invoker takes a

metho d index and all the arguments for an op eration and p erforms the

corresp onding metho d The following example illustrates this

define makesimplecell

let dispatcher

lambda op

cond eq op fetch

eq op store

else nothandled

lambda value

makeinstance

dispatcher

lambda index self args

apply case index

lambda self value

lambda self newvalue

set value newvalue

self args

Notice that instances returned by makesimplecell use the same dis

patcher We can arrange for the keys to the dispatch table here implemented

by cond not to change by having the dispatcher make copies of the relevant

global variables

We are free to implement the mapping p erformed by the dispatcher and

the mapping p erformed by the invoker as we see t The choices of cond

and case resp ectively are exp ository

The co de for p erforming op erations must b e changed so that it calls b oth

the dispatcher and the invoker

define operateas component selector composite args

let token gettoken component selector

if eq token nothandled

apply defaultbehavior selector composite args

apply invokemethod composite token args

define gettoken component selector

if instance component

instancedispatcher component

selector

getnoninstancetoken component selector

define invokemethod component token composite args

apply if instance component

instanceinvoker component

noninstanceinvoker component

token composite args

Fast metho d invocation

To reduce the amount of time sp ent in the storage allo cator and garbage

collector we would like to avoid allo cating a new closure every time the in

voker applies a metho d Because the metho d is only called from the invoker

the compiler can customize the calling sequence from the invoker to each

metho d The environment for each metho d is a subset of the environment

for the invoker so each metho d can use the invokers environment Thus the

co de for the invoker reduces to no more than a jump through a branch table

2

to the appropriate metho d The arguments are simply passed through

If we assume the general calling sequence puts a p ointer to the callees envi

ronment in a register then the co de for the metho ds can access their lo cal

state as indirect loads o that register

2

In practice having the compiler recognize that the invoker has exactly the right form

might b e more trouble than having the ob ject system introduce a new primitive the

compiler can recognize We leave this to the implementors

assume rst argument is in A

load tablepcaa

jump a

table address of co de for metho d

address of co de for metho d

method

method

Happily this style of transformation has b een part of the Scheme cul

ture since near its inception More recently the T compiler

p erforms a similar set of transformations in compiling its variant of

makeinstance For a Scheme compiler already p erforming environment

and closure analysis only small changes are needed to implement invokers

eciently

Eciency of comp osite ob jects dispatch time revisited

The separation of an instance into an invoker and dispatcher makes it p os

sible for a comp osite ob ject to construct a single dispatcher that combines

the comp onent dispatchers Invokers corresp onding to the comp onent dis

patcher must also b e combined into a single invoker A constructor for a

comp osite instance with two comp onents in addition to its own b ehavior

might lo ok roughly as follows

define constructor

let dispatcher

combinedispatchers dispatcher

dispatcher

simpledispatcher

lambda a b c

makeinstance

dispatcher

combineinvokers invoker

invoker

simpleinvoker

The metho d index returned by the dispatcher in the last example is an

integer We call such a dispatcher a simple dispatcher Its corresp onding

invoker is a simple invoker

A dispatcher created by combinedispatchers returns a metho d in

dex that is a pair invoker number integer index An invoker returned by

combineinvokers p erforms a two stage dispatch based on such a metho d

index The invoker number selects a simple invoker and the integer index

is passed to that invoker to p erform the metho d The system can b e imple

mented such that there are only these two kinds of invokers and dispatchers

by having combinedispatchers combineinvokers always create struc

tures containing only simple dispatchers invokers

The implementation of combinedispatchers and combineinvokers

requires that dispatchers and invokers b e able to divulge some information

ab out themselves This is easy if dispatchers and invokers are themselves

instances

Caching

Many ob ject system implementations p erform some variety of caching to

minimize the amount of time in op eration dispatch The introduction of

dispatchers makes a variety of caching strategies easy in our framework

to o For the sake of caching the dispatcher plays the same role as the

class plays in other ob ject systems For caching to work correctly the

dispatchers must b e pure functions Unfortunately the dispatcher given for

makesimplecell dep ended on the values of global variables which could

change at runtime Reco ding the dispatcher to make private copies of the

relevant global variables xes the problem

An example

The example program given here illustrates multiple inheritance sending to

self and sending to a comp onent

To improve readability and hide the details of the ob ject system imple

mentation some syntactic sugar is introduced for expressions that create

instances and dispatchers An expression of the form

dispatcher disp disp

1 2

op op

1 2

yields a dispatcher for instances that handle the op erations op directly and

i

have comp onents with dispatchers disp disp An expression of the form

1 2

instance disp

component component

1 2

op formal formal body

1 11 12 1

op formal formal body

2 21 22 2

yields an instance with comp onents component component and meth

1 2

o ds

lambda formal body

1i i

for the corresp onding op erations The op erations and their order in the

instance and its comp onents must match those of the given dispatcher

The example denes a kind of cell that maintains a history of all the

values that have b een stored into it These cells are implemented as ob jects

that have two comp onents a ltered cell section and a sequence

The cells history may b e accessed using sequence op erations

Sequences

define seqref makeoperation f

define seqset makeoperation f

define seqlength makeoperation f

define sequencedispatcher

dispatcher seqref seqset seqlength print

define makesimplesequence size

let v makevector size

instance sequencedispatcher

seqref self n

vectorref v n

seqset self n val

vectorset v n val

seqlength self

vectorlength v

print self port

format port Sequence s seqlength self

A sequence is an ob ject that b ehaves just like a vector but is manipulated

using generic op erations

Filtered cells

define fetch makeoperation f

define store makeoperation f

define celldispatcher

dispatcher fetch store print

define makefilteredcell value filter

instance celldispatcher

fetch self value

store self newvalue

if filter newvalue

set value newvalue

discard self newvalue

print self port

format port Cell s value

Cells with history

define position makeoperation f

define discardedvalue makeoperation f

define discard

makeoperation

lambda cell value

format t Discarding s value

define cellwithhistorydispatcher

dispatcher celldispatcher

sequencedispatcher

position

store

discard

discardedvalue

print

Cells with history continued

define makecellwithhistory initialvalue filter size

let cell makefilteredcell initialvalue

filter

seq makesimplesequence size

mostrecentdiscard f

pos

let self

instance cellwithhistorydispatcher

cell seq

position self pos

store self newvalue

operateas cell store self newvalue

seqset self pos newvalue

set pos pos

discard self value

set mostrecentdiscard value

discardedvalue self

mostrecentdiscard

print self port

format port

Cellwithhistory s

fetch self

store self initialvalue

self

The two metho ds for the store op eration together with the somewhat

frivolous discard op eration illustrate sending to self and sending to a com

p onent The store metho d for cells with history overrides the store

metho d from the cell comp onent It invokes the store op eration on the

comp onent using operateas The comp onents metho d in turn calls a

discard op eration on the comp osite if the stored value fails to pass the

lter If the rst store metho d had simply invoked the store op eration

on the comp onent the discard would have b een applied to the comp onent

not the comp osite and the wrong metho d would have b een invoked

T ob ject Amos Amos Tektronix MacScheme Symbolics

system no cache with cache Smalltalk SCOOPS Flavors

by

by

by

pro c call

Table Comparative p erformance of ob ject systems op erations p er second

Role of the programming environment

We have not treated many problems that are usually addressed in ob ject

oriented programming languages For example when a constructor is re

dened instances that were created b efore the redenition are orphaned

they may not b e consistent with the new denition We consider this

a problem that should b e solved by the programming environment To do

this the programming environment may need to imp ose constraints on the

implementation of the ob ject system There is a similar problem asso ciated

with redening op erations

In our view there is nothing sp ecial ab out instances in this regard the

same problem comes up with pro cedures What should the programming

environment do ab out orphaned closures when the denition of the pro ce

dure that created them is mo died This is an orthogonal problem area

that should b e solved indep endently of ob jectoriented programming

In our system metho ds for a comp onent must b e dened monolithically

Again the task of managing distributed denitions can b e the resp onsibility

of the programming environment

Exp erimental results

The design describ ed here is essentially the same as the T ob ject system

ab out which little has b een published T itself is describ ed in and

Ts ob ject system including anonymous op erations and single inheritance

has b een in pro duction use since and its ob ject system has proved to

b e quite valuable Instances are implemented just as compactly as closures

an instance with n instance variables generally consumes only n words

of storage Recently a form of multiple inheritance join has b een added to

T but T do es not yet have any equivalent of dispatchers Metho d lo okup is

by linear search and in the case of multiple inheritance op eration dispatch

p erforms one pro cedure call for each comp onent

We have measured one asp ect of the p erformance of various dynamic

language ob ject systems number of op erations sends p er second that can

b e p erformed on an instance The data app ear in Table Our goals were

to compare an implementation based on our design to other dynamic

language ob ject systems and to assess the eect of adding dispatchers to

Ts ob ject system Of the implementations measured Tektronix Smalltalk

and Symbolics Flavors are considered to b e high p erformance

We p erformed three b enchmarks by measures the time to p er

form an op eration on an instance of one comp onent with one op eration

by measures the time to p erform an op eration on an instance of

comp onents each comp onent handling op erations similarly by

measures instances of comp onents each comp onent handling op er

ations We measured number of pro cedure calls p er second in the various

implementations as a reference to which to compare the other measurements

We measured several implementations including a prototype of our de

sign with dispatchers in an almost p ortable subset of T We refer to this

prototype as Amos for a minimal ob ject system Amos uses linear search

for metho d lo okup but it do es combine comp onents We also measured

a version of Amos which maintained a small metho d lo okup cache in each

op eration

For the T ob ject system the compiler p erforms the analysis describ ed

ab ove and the co de for op erations essentially operate and its subfunctions

is handco ded assembly language

SCOOPS is an ob ject system for Scheme based on Flavors MacScheme

SCOOPS is an implementation of SCOOPS quite sp ecic to MacScheme

Tektronix Smalltalk and Amos with cache use metho d lo okup caches

Symbolics Flavors uses a hash table for metho d lo okup

The T ob ject system Amos and Tektronix Smalltalk were measured on

comparable Mhz Motorola Unix systems MacScheme SCOOPS

was measured on an Apple Macintosh II a Mhz Symbolics

Flavors was measured on a Symbolics In overall p erformance for the

sort of co de tested the is considered as much as twice as fast as the

Mhz systems tested

The results show that dispatchers are eective and that our design can

b e implemented with eciency comparable to other dynamic language ob

ject systems Because Amos and the T ob ject system use linear search for

metho d lo okup p erformance falls o with increasing numbers of op erations

that the instance handles T ob ject system p erformance also decreases with

increasing number of comp onents b ecause it do es not combine the comp o

nents in any way Amos do es not have this problem

For instances with small numbers of metho ds and comp onents the T

ob ject system is comparable to the other systems measured The addition

of dispatchers would make it comp etitive for instances with larger numbers

of op erations and comp onents

Because the b enchmarks are so simple any sort of caching is extremely

eective In practice we exp ect the linear search in dispatch will slow the

system substantially for instance handling many op erations Replacing the

linear search with hashing is practical for Amos but not for T b ecause Amos

combines dispatchers

Comparison with other work

Existing Lispbased ob jectoriented languages include Flavors the Com

mon Lisp Ob ject System CLOS and CommonOb jects All of these

systems are substantially more complicated than our prop osal particularly

in their treatment of metho d combination and multiple inheritance They

extend the underlying language with a new kind of variable instance vari

ables Instance variables are not lexically scop ed since their scop e ie the

program text for metho ds of the corresp onding class is not textually related

to their p oint of denition the class denition Flavors and CLOS sup

p ort follow our approach of implementing anonymous generic op erations as

pro cedures CommonOb jects shares some of our goals particularly strong

supp ort for encapsulation

Smalltalk makes no distinction b etween language and environment It

includes many features that defeat encapsulation as such features tend to

make the job of the programming environment easier a Smalltalk priority

Our applicative bias is apparent in our design in that there are no ini

tialization metho ds and there are no sideeects to invokers our analogue

of classes Initialization is done applicatively in the contructor pro cedures

rather than by metho ds that sideaect an instances state Sideaecting a

class is a common way to achieve metho d denition in other systems

Our call op eration corresp onds to the value message in Smalltalk and

pro cedures play the role of Smalltalk blo cks by handling the call op eration

However Smalltalks construct for creating blo cks is unrelated to the con

struct for creating other kinds of ob jects This app ears to b e an unnecessary

source of language complexity

Oaklisp also aims for minimality As in our system Oaklisp can

dene lambda in terms of ob ject system primitives In Oaklisp however

pro cedures are degenerate generic op erations whereas in our system pro ce

dures are degenerate instances While we retain Schemes lexical scoping

Oaklisp has two kinds of bindings and scop e rules formal parameters are

lexical and are b ound in the usual way while instance variables are dened

by the class denition which cannot in general b e statically related to

the p oints of use of the instance variables Also while we retain Schemes

almostapplicative style Oaklisp relies on sideeects for dening metho ds

and initializing instance variables

As formulated here anonymous op erations are essentially capabilities

An op eration is an unforgeable token that gives a particular kind of access

to some otherwise opaque ob jects

Conclusions

We have shown how to add ob jectoriented programming facilities to Scheme

with only small additions to the language In fact the ob ject system can b e

explained in p ortable Scheme with the addition of a single new but simple

primitive type The system supp orts applicative programming style which

to our knowledge is unique among Lispbased ob jectoriented programming

systems For eciency we dep end on known and implemented compilation

techniques for Scheme

The programmers interface to the ob ject system needs work With

the syntax describ ed in Section the programmer must make sure the

dispatcher agrees with the invoker This annoying problem arises from the

great exibility our system has in creating ob jects We can cop e with this

redundancy in any of several ways Eliminate it by introducing some kind

of constructor syntax This might require the addition of automatically

generated initialization metho ds and thus side eects which we prefer to

avoid Check it dynamically at instance creation timethe necessary

information is available but this is exp ensive with one comparison p er

op eration handled by the instance Check it statically using something

like a Milnerstyle type inference system

We b elieve that it is p ossible to build a programming environment as

go o d as Smalltalks without sacricing supp ort for encapsulation

Acknowledgements

Kent Pitman worked with us on the original formulation of the T ob ject

system and was its rst user Richard Kelsey David Kranz and Jim Philbin

help ed make Ts ob ject system fast Will Clinger suggested that the T ob ject

system could b e made more ecient by introducing an explicit analogue of

classes and encouraged us to work out the details Will Clinger Ken Dickey

Bill Havens Uwe Pleban Steve Rehfuss and Steve Vegdahl provided helpful

comments on drafts of the pap er

References

Gul A Agha Actors A Model of Concurrent Computation in Dis

tributed Systems MIT Press Cambridge MA

Patrick J Caudill and Allen WirfsBro ck A Third Generation

Smalltalk Implementation SIGPLAN Notices

Thomas J Conroy and Eduardo PelegriLlopart An Assessment

of Metho dLo okup Caches for Smalltalk Implementations in

Smal ltalk Bits of History Words of Advice G Krasner ed

AddisonWesley

J Dennis and E Van Horn Programming semantics for multipro

grammed computations Communications of the ACM

Richard P Gabriel et al Common lisp ob ject system sp ecication

ANSI XJ Do cument

Adele Goldb erg and David Robson Smal ltalk the language and its

implementation AddisonWesley

James Kempf et al Exp erience with CommonLo ops SIGPLAN No

tices

David Kranz et al Orbit an optimizing compiler for Scheme SIG

PLAN Notices

David Andrew Kranz Orbit An Optimizing Compiler for Scheme

PhD Thesis Yale University May

Kevin J Lang and Barak A Pearlmutter Oaklisp an ob jectoriented

Scheme with rst class types SIGPLAN Notices

Henry Lieb erman Using prototypical ob jects to implement shared b e

havior in ob jectoriented systems SIGPLAN Notices

David A Mo on Ob jectoriented programming with avors SIG

PLAN Notices

Jonathan A Rees and Norman I Adams T a dialect of Lisp or

lambda the ultimate software to ol In Conference Record of the

ACM Symposium on Lisp and Functional Programming

Jonathan A Rees and Norman I Adams The T manual fourth edi

tion Yale University Computer Science Department

3

Jonathan A Rees et al Revised rep ort on the algorithmic language

Scheme SIGPLAN Notices

Alan Snyder CommonOb jects an overview SIGPLAN Notices

Alan Snyder Encapsulation and inheritance in ob jectoriented pro

gramming languages SIGPLAN Notices

Guy L Steele Jr Lambda the ultimate imp erative MIT AI Memo

Guy L Steele Jr Lambda the ultimate declarative MIT AI Memo

Guy L Steele Jr Rabbit a compiler for Scheme Technical Rep ort

MIT AI Lab

Lynn Andrea Stein Delegation is inheritance SIGPLAN Notices

Gerald Jay Sussman and Guy L Steele Jr Scheme an interpreter for

extended lambda calculus MIT AI Memo

Daniel Weinreb and David Mo on Lisp Machine Manual MIT AI Lab