The reexive CHAM and the joincalculus

Cedric Fournet Georges Gonthier

CedricFournetinriafr GeorgesGonthierinriafr

INRIA Ro cquencourt

Le Chesnay Cedex

FRANCE

y

Octob er

Abstract

By adding reexion to the chemical machine of Berry and Boudol we

obtain a formal mo del of concurrency that is consistent with mobility and

distribution Our mo del provides the foundations of a

with functional and ob jectoriented features It can also b seen as a pro cess

calculus the joincalculus which we prove equivalent to the calculus of

Milner Parrow and Walker

Intro duction

There is a mismatch between calculi for concurrent pro cesses and languages for

programming distributed and mobile systems Calculi such as CCS or the

calculus intro duce a small number of constructs and have a thoroughly

studied metatheory However they are mostly based on atomic nonlo cal interac

tion typically rendezvous which is dicult to implement fully in a distributed

setting Programming languages such as Actors or Obliq have separate

primitives for transmission and synchronization for instance remote pro cedure

call and semaphores However they also have a much larger set of constructs

usually including imp erative primitives and this hinders their formal investiga

tion

To bridge this gap weintro duce a new elementary mo del of concurrencythe

reexive chemical abstract machine We b oth use this mo del as the basis for a

practical programming language design and study this mo del formally using a

pro cess calculus the joincalculus

The reexive CHAM mo del is obtained from the generic CHAM by imp osing

lo cality and adding reexion Lo cality is achieved by barring nonlinear reaction

patterns this implies that each reaction rule or molecule can be asso ciated with

y

To app ear in POPL Also available electronically from INRIA

This work is partly supp orted by the ESPRIT Basic Research Action CONFER

a single reaction site Reexion is added by letting reactions extend a machine

with new kinds of molecules along with their reaction rules this lets our mo del b e

computationally complete Our mo del is more eective than the generic CHAM

molecules travel to their reaction site instead of having to mix and match It also

turns out that the sequential deterministic subset of our mo del is basically the

continuationpassing style calculus hence we can embed the calculus using

any CPS transform

Our language design extends a higherorder sequential language with paral

lelism in expressions with fork calls and in function patterns with join pat

terns Jointly dened functions provide the same synchronization capabilities as

synchronous channels or concurrent ob jects Moreover join patterns are more

consistent with lexical scop e they statically bind joint function calls to abody

of co de whereas the binding of messages to receptors is dynamic

The joincalculus is simply the syntactic description of the reexive CHAM

molecules It is quite similar to the calculus except that it combines restriction

reception and replication in a single joint receptor denition Our main theorem

states that the calculus and the joincalculus have the same expressivepower up

to weak barb ed congruence it is obtained by exhibiting fully abstract enco dings

in each direction As a result we can exp ect most of the calculus metatheory to

carry over directly to the joincalculus

Overview

Most pro cess calculi are based on synchronous channels A is an ab

straction of the communication media on which data is exchanged send and re

ceive op erations on channels provide a concise denotation for the transmission

routing and synchronization that actually occur in a concurrent system The

calculus has demonstrated that in combination with an elegant scop e

management technique channel op erations are computationally complete The

PICT exp eriment has further shown that the calculus more sp eci

cally its asynchronous fragment can b e used as the basis of a useful higherorder

concurrent language in a nondistributed setting

In a distributed setting however channels intro duce atomic interaction be

tween distant emitters and receivers communication in the ether This can

b e dicult to implement even more so if recovery from lo cal failures is also sup

p orted unless the channel implementation includes a sophisticated faulttolerant

consensus proto col some of the implementation details will be revealed by fail

ures This problem o ccurs even in the asynchronous setting as there is interaction

between distant receivers through contention

On the other hand channels are not absolutely required for highlevel dis

tributed programming For instance they are not primitive in ob jectbased lan

guages unfortunately these languages lack an abstract foundation as simple

and precise as the calculus It is such a mo del that we purp ort to develop in

this pap er Our starting point will be the chemical abstract machine which can

b e regarded as the computational mo del of the calculus

Litterally CHAM interaction is lo cal since molecules simply move around in

a solution until they meet in matching pairs and react but the random mo

tion in this description is not very eective Assuming that the chemical rules

have disjoint domains the CHAM also has a more op erational interpretation all

molecules travel to a reaction site asso ciated to their rule where they are sorted

matched and made to react guratively reactions are catalyzed at the sites

Under this interpretation however the CHAM is not very concurrent com

munication is centralized in a xed set of sites catalyzers are b ottlenecks and the

managementofeach site is complex as the numb er of dierent exp ected molecule

shap es can grow arbitraly catalyzers clog up It would b e much b etter to have

a larger number of sites with simpler matching instead and this is exactly what

the reexive CHAM mo dications bring in by allowing dynamic creation of sites

and restricting reaction patterns

Wenowsketch the basic mechanisms of the reexive CHAM the formal deni

tion is exp osed in section Our mo del op erates on higherorder solutions RM

comprising two multisets The molecules M represent the pro cesses running in

parallel the reactions R dene the current reduction rules

Names are the only values in our mo del as in the calculus They have a

twofold usage p ort names and transmitted values We write xhy i to mean that

the name y is sent on the name x

An atom is a p ending message xhy i A comp ound molecule consists of several

submolecules glued by the join op erator j Molecules can b e heated into smaller

ones in a reversible way As a rst example we consider a print sp o oler with two

p orts available printers like laser send their name on the p ort named ready while

users send the lenames to b e printed on the p ort named job There are three

atoms in solution on the rst line versus one atom and one comp ound molecule

on the second line where the molecule joins the laserprinter and the le The

structural equivalence relates these two solutions without reactions yet

readyhlaseri jobh i job h i

readyhlaserijjob h i job h i

Denoted or JP a reaction consumes comp ound molecules that have a sp e

cic join pattern J and pro duces new molecules in the solution that are copies of P

where the formal parameters of J have b een instantiated to the transmitted values

This corresp onds to reduction steps on the whole solution RM RM

Continuing our example we add a reaction that matches printers and jobs then

sends the lename to the printer

D readyhprinter ijjob hlei printerhlei

We now add this chemical reaction in our solution and we use it to reduce our

previous molecule and generate a new atom Notice that nondeterminism comes

and is just committed by the reaction from

D readyhlaserij job hi jobh i

D laserh i jobh i

Our mo del is reexive meaning that reactions can b e dynamically created This

is done by our last kind of molecule The dening molecule def D in P can be

heated in two parts a new reaction D and a molecule P In this case the newly

dened p orts can b e used in b oth Q and P The solution we just considered could

have come from a single molecule with the structural rules

def D in readyhlaserijjob h ijjob h i

D readyhlaserijjob h ij jobh i

D readyhlaserijjob h i jobh i

A more realistic sp o oler would send the name job to its users and the name ready

to its printer drivers This corresp onds to the wellknown scop eextrusion of the

calculus However our denitons have a strict lexical discipline the b ehaviour of

ready and job may not b e deterministic but it is statically dened Other pro cesses

that receive these names may send messages but they cannot add new reactions

for them This essential restriction to reexion lets us extend the language safely

For instance sp ecial names used only in rules may be added to the machine

without sp ecial care while in the calculus any pro cess may mistakenly alter

their b ehaviour

In section we expand the mo del into a simple programming language with

mobility and we illustrate some of its features From the programmers p oint of

view it is a highlevel concurrent language with lexical scop e and asynchronous

messages We identify function calls as a sp ecial case of with

CPS we analyze two reduction strategies for the calculus then we dene some

convenient syntactic sugar for sequential control

The language also has ob jectoriented features Elementary ob jects are dened

by new names and new reaction rules metho ds are the names that are returned

behaviours are declared in the rules states are held in messages on internal names

Elab orate synchronization schemes can b e expressed among these concurrent ob

jects by patternmatching on their rules Our rm commitment to lexical scoping

makes our ob jects very static meaning that more imp erative features such as

cloning must b e explicitly enco ded

In sections and we explore the prop erties of the joincalculus and its re

lation to the calculus The joincalculusis the pro cess calculus induced by the

reexive CHAM We rst dene the observational equivalence then we use it as

a basis to compare the relative expressive powers of dierent calculi Our trans

lations between calculus are proved fully abstract with regards to weak barb ed

congruence in that sense our technical results are precise upto substitution of

enco dings in anycontext of the host calculus In section we strip the joincal

culus of convenient but unnecessary features recursion join patterns including

more than two messages p olyadic messages denitions with several clauses and

we obtain a core joincalculus that retain the expressive power of our mo del In

section we compare this core joincalculus and the asynchronous calculus

In spite of signicant dierences b oth calculi provide exactly the same expressive

power However their scoping conventions makes the accurate enco dings surpris

ingly complex We present b oth simple and accurate enco dings and we discuss

their characteristics which illuminate what separates the two calculi

We conclude the pap er with a few words on future work An implementation

is under waytoevaluate our language in practice and wemention the extensions

to supp ort typ es explicit distribution failuredetection and migration

In the annexes A and B wesketch the pro ofs of full abstraction for the two en

co dings b etween the calculus and the joincalculus that are describ ed in section

These results are obtained using auxiliary enco dings and bisimulationbased

techniques in particular weak bisimulation upto expansion as prop osed in

Related work

To our knowledge Banatre was the rst to suggest multifunctions as prim

itives for synchronization They corresp ond to a rstorder version of our join

denitions in a pro cedural and synchronous language Our work is more directly

related to the recent asynchronous trend of the calculus and from

its rst applications

Our calculus fo cuses on mobility in a minimal setting This contrast with

extensions for concurrency from an ob jectoriented or a functional kernel

Likewise distributed systems built on the actor paradigm prop osed a two

layered architecture with a functional kernel wrapp ed in an imp erative extension

for communication

Other calculi intro duce concurrency andor distribution using dierent prim

itives Instead of directed communication with a functional avour they rely for

instance on unication and broadcast This is the case for Oz and for linear

ob jects

The reexive chemistry

We rst give the syntax of pro cesses and the scop e for their names Then we

present the reexivechemical machine and we illustrate it on a few simple exam

ples

Names Pro cesses Denitions

Values in the reexive CHAM are only names as this is the case in the calculus

Let N be an innite set of names we use name variables in lowercase letters

e

x N to denote its elements In the following x is a notation for a tuple of name

variables x x x

 n

The following grammar denes pro cesses joinpatterns and denitions A

e

pro cess P is an emission of an asynchronous p olyadic message xhv i a denition of

new names or a parallel comp osition of pro cesses A denition D consists of one

or several elementary denitions J P that match patterns J joining messages

to guarded pro cesses P connected by the op erator It entirely describ e the

behaviour of its dened names

def def def

e e

P xhv i J xhv i D JP

def D in P J jJ D D

P jP

Names that app ear in a pro cess P may be captured by an enclosing deni

tion The only binder is the join pattern J but the scop e of its names dep ends

of their p osition in messages The formal parameters that are received are b ound

in the corresp onding guarded pro cess The dened p ort names are b ound in the

whole dening pro cess that is the main pro cess and recursively all the guarded

pro cesses Received variables rvJ dened variables dv J and dv D and free

variables fvD and fvP are sp ecied by structural induction Notice the syn

tactic restriction for pro cesses No received variable may app ear twice in the same

pattern J This rules out any comparison on names and guarantees that join

patterns remain linear

def

e e

rvxhv i fu v g

def

rvJ jJ rvJ rvJ

def

e

dv xhv i fxg

def

dv J jJ dv J dv J

def

dv JP dv J

def

dv D D dv D dv D

def

fvJP dv J fvP rvJ

def

fvD D fvD fvD

def

e e

fvxhv i fxgfu v g

def

fv def D in P fvP fvD dv D

def

fvP jP fvP fvP

A name is fresh with regards to a pro cess or a solution when it is not free in

x

them In the following we use substitutions and f g with p ossibly implicit

y

renaming on nonfree variables to avoid name clashes

While this is not needed in the joincalculus we will assume that for any

given name variable the numb er of arguments is the same in every message and in

every joinpattern Formally this amounts to use a recursive sort discipline and

to consider only wellsorted pro cesses as for the calculus

Op erational semantics

We extend the chemical approach of Berry and Boudol with reexion We rst

This corresp onds to the underlying give some heatingco oling reversible rules

structural equivalence on pro cesses and includes reexion Once molecules have

b een suitably dissolved the single reduction rule expresses the mechanism of

communication in a much simpler way than for the calculus

Rules op erate on higherorder solutions R M On the righthandside

active pro cesses are molecules in the multiset M on the lefthandside active

denitions are reactions in the multiset R For the sake of simplicity we only

mention the elements of b oth multisets that participate in the rule separated by

commas

strjoin P jQ P Q

strand D E D E

strdef def D in P D P

dv dv

red JP J JP P

rv rv

Sideconditions for substitutions

strdef instantiates the port variables dv D to distinct fresh names

dv

Dom fvRM

dv

red substitutes the transmitted names for the distinct received variables

rv

rvJ

The rst two structural rules express that j and are commutative and

asso ciative strdef describ es the heating of a molecule that denes new names

The restriction on is reminiscent of the restriction prex in the calculus

dv

with regards to scop e extrusion and at the same time enforces a strict static scop e

for the denitions red is a meta reduction rule that asso ciates the actual reduc

tion rule to each reaction in R In one step such reductions consume

any molecule with a given p ort pattern make a fresh copy of their guarded pro

cess substitute its received parameters for the sent names and release the pro cess

as a new oating molecule

Some examples

We now give examples of pro cesses and denitions along with an intuitive de

scription of their meaning The formal treatment of observations is deferred until

section

def xhui yhui in P

def y hui xhui in def xhui yhui in P

def x huijx hv i xhu v i in P



def xhv ijy hi hv i in P

def shi P shi Q in shi

def oncehijy hv i xhv i in y hijy hijy hijoncehi

def l oophi Pjl oophi in loophijQ

The simpler denitions p erform some wiring between names in messages on

the lo cal name x in P are forwarded to the outside as messages on y in the

leftmost x is a free name while the rightmost one is lo cally b ound in P and

will require renaming however messages on the lo cal x are still forwarded in two

steps on the external one p erforms multiplexing of messages on x whose parts

are supplied on x and x was intro duced as a print sp o oler in the overview



but it more generally mo dels calculuslikechannels as values are sentonx and

requests for values are sent on y to me matched in the denition and

b oth express internal nondeterminism P Q using a comp ound denition and

xhi xhi xhi using the message on once as a lo ck replicates the pro cess

P starting a new copyeach time the denition is used

We nish our series with a longer example that illustrates b oth higherorder

and the use of internal messages to store some lo cal state A reference cell ab

straction is dened as

def gethijshv i hv ijshv i

C B

sethu ijshv i hijshui

def mk cel l hv i

A

 

in shv ij hg et seti

 

Each mk cel l message triggers the external denition which in turn denes three

fresh names g et set s The rst two are sent backon for later access or up date



to the new cell Thanks to lexical scoping the last name s remains lo cal and the

initial message shv i together with the two internal rules guarantee the invariant



of the cell there is exactly one message on swhichcontains the currentvalue

Programming in the joincalculus

Wenow use the reexive CHAM as the foundation of a concurrent programming

language While our mo del already provides enough expressivepower its features

are to o lowlevel for actual programming For instance there is no convenient

way to express sequential control in a pro cess which strongly suggest the use of

some syntactic sugar We rst study the emb edding of higherorder functional

programming using continuationpassing styles we enco de two reduction strate

gies for the calculus in clearcut subsets of the joincalculus Then we describ e

a toy concurrent language based on these ideas and we give some programming

examples We nally discuss ob jectoriented features programming

Two enco dings of the calculus

Denitions of the form def f hxi P in Q seems to b e very similar to the let

f xE in E statement in In particular they share

the same static scoping discipline The ma jor dierence comes from asynchrony

in our mo del meaning that wemust explicitly create and send continuations

For a given CPS we enco de terms as pro cesses that can b e triggered and we

compare their resp ective b ehaviour With minor adaptations we obtain results of

adequacy similar to those for the calculus The terms and their translations

converge or diverge accordingly Our purp ose here is to illuminate the tight con

nection b etween functions and joindenitions which makes our enco dings simpler

than Our syntax for the calculus is as usual

def

T x j xT j TT

Callbyname in this reduction strategy terms are reduced in leftmost

order and no reduction may o ccur under a Our enco ding is

def

x xhv i

v

def

xT def hx w i T in v hi

v w

def

TU def xhui U

v u

in def w hi hx v i in T

w

Intuitively the pro cess T sends its value on v a value is a pro cess that

v

serves evaluation requests sent on and requests supply two names x to send

requests for the value of the argument and w to eventually return a value when

evaluation converges

The image of the translation is exactly the deterministic subset of the join

calculus dened as the set of pro cesses that contain no parallel comp osition and

neither joinpattern nor in denitions As exp ected reductions for pro cesses

in this subset are entirely sequential

Parallel callbyvalue the term TU can b e reduced as so on as b oth T

and U have b een reduced to values thus allowing the function and the argument

to be evaluated in parallel Again no reduction may o ccur under a Using a

larger subset of the joincalculus we enco de this conuent but nondeterministic

reduction strategy

def

x v hxi

v

def

xT def hx w i T in v hi

v w

def

def thijuhw i hw v i in T j U TU

t u v

Again the enco ding T sends its value on v and a value is a pro cess that

v

serves evaluation requests senton but evaluation requests now supply the value

of the parameter along withanameforthevalue of the term

The image of the translation now uses parallel comp osition to capture the

nondeterminism of the strategy The symmetry between the evaluation of the

function and of the argument is apparent backed by the two symmetries on the

fork of evaluation requests and on the join of their results

A language with sequencing

In our basic mo del synchronization happ ens only as molecules are consumed and

this suces to express control ow In practice however the resulting programs

would contain many explicit continuations and would b e dicult to understand

Instead we make the sequential control apparent we x a CPS and provide it

as syntactic sugar in the language To this end the new grammar extends the

syntax in two steps

Names are split in two families synchronous and asynchronous

Pro cesses can consist of series of instructions fI g that are executed sequen

tially

def

e

P xv asynchronous message

fI g sequence of instructions

P jP parallel comp osition

def

I def J P and J P recursive denition

e

let v V named values

run P asynchronous pro cess

e

do f V synchronous call

if V then I else I conditional

e

return V to f implicit continuation

def

V v value name

e

f V synchronous call

def

e

J xv asynchronous message

e

f v synchronous message

J jJ join of several messages

As in the calculus Asynchronous names x are dened and used for asyn

chronous messages Synchronous names f are names that implicitly transmit a

continuation in every message We extend the sort discipline to distinguish names

consistently Whenever a message is sent to a synchronous name a continua

tion channel is dened as the remaining part of the current instruction sequence

and the continuation is added to the message Whenever such a message is re

ceived as part of a join pattern the continuation is b ound in the corresp onding

guarded pro cess and maybeusedtosendback results using the return instruc

tion Briey let binds names from synchronous calls do do es the same when the

result is a synchronisation signal run asynchronously forks a pro cess return

asynchronously sends results back on the continuation that was received on f

Finally any value maycontain nested synchronous calls The formal translation

is omitted

While the underlying mo del is the same this smo othly merges in a declarative

style some nondeterministic programming in a functional framework For de

nitions with only one message in their pattern as is particular for continuations

the substitution lemma holds as the instantiated b o dy can b e substituted for the

calling message as in any functional language

In our examples synchronous names are capitalised for instance the mk cel l

example is the compilation of the program

def MKCELLv

def GET sv sv return v to GET

and SETu sv su return to SET

run sv

return GETset to MKCELL

The second example elab orates on the print sp o oler of the overview in an imp era

tivestyle Now the user select a printer and a format and les are prepro cessed

accordingly b efore printing The channels PRINT and ENSCRIPT are synchronous

calls to the library At runtime the les letter and note are transcripted and

laserprinted then the current printer is changed then the le drawing is printed

in colour

def NEWPRINTERPRINTformat current

run currentPRINTformat

return to NEWPRINTER

and JOBfile currentPRINTformat

run currentPRINTformat

do PRINTENSCRIPTfileformat

return to JOB

run currentLASERps

do JOBletter

do JOBnote

do NEWPRINTERcolourpscolour

do JOBdrawing

While this style mostly comes from the design of PICT the functional

syntax for emissions and the static denition of receptions make it more direct

and allow a ner control The main drawback is that whenever a PICT channel

is actually used with several emitters and several receptors in parallel it must

b e compiled into a joindenition see example fortunately this is uncommon

in programming examples Our approach also oers more declarativeness than

ob jectbased languages since there is no need to mutate systematically the recep

tor

Concerning the implementation the set of rules that comes from a denition

is indep endentfromany other denition Taking advantage of asynchrony these

rules are managed lo cally by queues for messages and by an automaton that

matches them with join patterns and forks accordingly the guarded pro cesses To

this end wellknown compilation techniques are available Besides the em

b edding of large functionalstyle denitions can b e made reasonably ecient using

tailrecursionlike optimizations Finally concrete values and builtin functions

can easily be added The behaviour of their reserved names is given by sp ecic

rules that describ e the consumption of their messages and are implemented as

lowlevel function calls

Concurrent ob jects and synchronization patterns

Our mo del provides the essential features of ob jects as is already the case for the

calculus First we consider primitive ob jects that are already present in

the language Using messagepassing and patternmatching in our denitions we

enco de ob jects as servers that receive requests to execute their metho ds

The design of a fulledged ob jectoriented language would require some more

enco ding For instance inheritance or cloning is not primitive Wesketchsome

features to supp ort more general ob jects with dynamic denitions and inheritance

Primitive ob jects

Ob jects are created in denitions whose p ort names may b e either returned and

made public or kept private in the b o dy of their denition In that sense our cell

example is a simple primitive ob ject We identify names and metho ds denitions

and active concurrent ob jects The current state of an ob ject can be split into

several comp onents held on internal messages according to the critical sections

Besides the interface may feature several states with dierent synchronization

capabilities The declarative patternmatching on join messages is much more

expressive than the serialization of metho d calls It contains the expressiveness of

coloured Petri nets and can even b e dynamically expanded

We illustrate the combination of concurrency and synchronization on the ex

ample of priority queues gure

def MKPRIORITYQUEUE

def EMPTY none

run none

return TRUE to EMPTY

and EMPTY somexEAR

run somexEAR

return FALSE to EMPTY

and ADDx none

return to ADD

let EAR MKPRIORITYQUEUE

run somexEAR

and ADDx someyEAR

return to ADD

do AMAX xy

run someMINxyEAR

and REMOVE somexEAR

return x to REMOVE

if I then run none

else run someREAR

run none

return EMPTYADDREMOVE to NEWPRIORITYQUEUE

Our priority queue features three synchronous metho ds EMPTY ADD REMOVE

with the exp ected meaning REMOVE retrieves the smallest value or blo cks until

a value is available There are two internal states none when empty and

somexEAR when containing the smallest value x in its head and another

priority queue with metho ds EAR in its tail Statically we can check that there

is always exactly one state message available for each denition Values can be

concurrently tested added and removed in particular a new some message is

released after at most one comparison when a new value is added while the up date

propagates toward the tail in parallel When the tail is eventually reached a new

empty priority queue is created using the recursive denition MK PRIORITY QUEUE

which returns three fresh metho ds on an emptypriority queue to b e stored in the

lastbutone some message

Classbased ob jects and inheritance

Our primitive ob jects lack dynamicity b ecause the lexical scop e of their deni

tions forbids overloading or cloning It is wellknown that inheritance and syn

chronization for concurrent ob jects do not merge gracefully in our case we can

recover adho c dynamicity using indirections In our sp o oler example a dynamic

metho d to print les is implemented bytwo static metho ds job for invo cation and

newprinter for overriding while the current name asso ciated with the metho d is

kept in the internal state currentprinter Likewise one can substitute state over

writing for metho d overriding in many cases and mix freely static and dynamic

comp onents within the same ob jects

While our solution seems b etter than the traditional ob jectasserver enco ding

it requires more than some lo cal syntactic sugar An alternative approach consists

in complementing the joincalculus with new features eg with more general

records to obtain richer primitive ob jects

The joincalculus

The joincalculus is simply the set of molecules of the reexive CHAM In this

section we study in more details its prop erties as a pro cess calculus we rst give

another equivalent denition of a variant of the joincalculus then we briey

discuss observation and we identify observational equivalence as a barb ed bisim

ulation congruence nally we use this to ol to precisely reduce the joincalculus

to its essential features

Our reexive chemical machine entirely denes the syntax molecules as pro

cesses the structural congruence and the reduction relation

Any chemical solution can be co oled down into a single pro cess wrapping all

the reactions in a big denition header Thus joincalculus pro cesses provide

another presentation of our mo del as a rstorder rewriting system mo dulo struc

tural equivalence This more syntactic approach is esp ecially useful to compare

our mo del to other calculi several subsets of the joincalculus in this section and

the calculus in the next one

The joincalculus as a pro cess calculus

The core recursive joincalculus is a restriction of the full calculus with simpler

denitions join patterns and messages Its syntax is given by the grammar

def

P xhui j P jP j def xhuijy hv i P in P

 

As b efore the scop e of u v is P whereas the scop e of x y extends to the whole

denition The structural congruence is the smallest relation such that for all

pro cesses P Q R S for all denitions D D suchthat dv D dvD contain only

fresh names

P jQ QjP

P jQjR P jQjR

P j def D in Q def D in P jQ

def D in def D in P def D in def D in P

P Q P Q

P Q P jR QjR

R S P Q def JR in P def JS in Q

Wenow dene the reduction relation as the transitions of a lab elled transition

system where ranges over fD gf g Our transition relation is the smallest

relation such that for every denition D xhuijy hv i R

D

s t

xhsijy hti R f g

u v

and for every transition P P

jQ P jQ P

def D in P def D in P if fvD dv

def in P def in P if

Q Q if P P and Q Q

Lemma The structural congruence is the smal lest congruence that contains

al l pair of processes P Q such that P Q The reduction relation

contains exactly the pairs of processes P Q up to such that P Q

Observation

While the observation of concurrent pro cesses is dicult in general the joincal

culus b enets from the exp erience gained from CCS and from the calculus After

an informal discussion of observation criteria weintro duce the equivalence among

pro cesses as the largest congruence with a few suitable prop erties thus following

the approach prop osed in for the calculus This provides an accurate

basis for comparisons with other calculi

What is observable

The only way for a pro cess to communicate with the outside is to exp ort some

names in messages on its free names and to wait for an answer from an enclosing

denition We distinguish pro cesses accordingly Toeach free name xwe asso ciate

an asynchronous outputonly barb which tests the ability of pro cesses to emit

x

anything on x In the following stands for any sequence of and

def

e e

P x fvP v R M P RMxhv i

x

Observational congruence

The congruence between pro cesses is the largest equivalence relation that is a

renement of the output barbs that is weakreductionclosed and that is a

x

congruence for denitions and parallel comp ositions P Q if P Q then

x N P implies Q

x x

P P implies Q Q Q and P Q

D def D in P def D in Q

R R jP R jQ

In most pro ofs we also need a ner auxiliary expansion relation and we

apply the bisimulation up to expansion technique the expansion between

pro cesses is the largest relation that veries prop erties like and suchthat

P Q if P Q then

Q Q implies P Q or P P P Q

For example wehave

fvP P

P Q P Q

xhui y hui

def z hti thui in z hxi def z hti thui in z hy i

z hxi z hy i

def uhz i vhz i in xhui xhv i

In no pro cess has any barb and reductions are simulated byno reduction on

the other side in and the two pro cesses dont have the same barbs in

the two names x and y can b e distinguished in contexts as in in two

distinct names are sent on x but their behaviour is the same in every context

although an internal reduction is needed to relayvalues from u to v

Despite technical dierences in their denitions is also the congruence over

all contexts that is obtained from the weak barb ed bisimulation whose barbs are

as dened for the calculus in Such barb ed congruences can b e dened

x

for many pro cess calculi indep endently of their syntaxes and wetake advantage

of this common framework to obtain precise results

Full abstraction

In all the following we assess the relative expressivepowers of miscellaneous calculi

from the existence of fullyabstract enco dings b etween them

Denition Let P P be two calculi with respective equivalences



P P P P

  

P is more expressive than P when there is a ful ly abstract encoding





from P to P for al l P Q in P we have



P Q P Q



 

P and P have the same expressive power when each one is more expressive



than the other

We use observational congruence as the reference equivalence for each pro cess

calculus meaning that our full abstraction results are up to observation in any

context This seems to be the nest results one could exp ect between dierent

pro cess calculi

Internal enco dings

The reexive CHAM mo del corresp onds to a joincalculus that is convenient as

the kernel of a programming language However it is p ossible to reduce it further

to simpler primitives To this end we successively remove recursive scop e deni

tions with several clauses D D joinpatterns with more than two messages and

messages with several transmitted values We replace them byinternal enco dings

which we prove to be fully abstract Our purp ose here is to isolate the essential

features of the joincalculus and to give some useful examples Of course all the

derived features would b e taken as primitives in a realistic implementation

Theorem The core joincalculus has the same expressive power than the ful l

joincalculus up to congruence in particular there is a ful lyabstract encoding

from the ful l calculus to the core calculus for al l processes Q R of the ful l



joincalculus

Q R Q R

 

The actual pro of consists of successive internal enco dings of redundant fea

tures in each part of this section we explain a stage of the enco ding We omit

the pro ofs Please note that the following enco dings have been chosen for their

accuracy with regards to observation and for their simplicity of exp osition as

a result they may use busywaiting and intro duce innite sequences of internal

reductions they are not meant to be used in practice to implement the features

that we remove from the joincalculus Indeed we plan to implement eciently

the full calculus directly from its reexivemachine sp ecication

Recursive binding

The nonrecursivevariant of the joincalculus is dened by restricting the scop e of

dened variables in def D in P to P only so that guarded pro cesses inside of D

cannot refer to them To get rid of the recursive usage of names in denitions our

enco ding simply shift the binding variables from denition to reception Another

name is dened to hold formerly recursive names and a message containing the

recursive names is always available on it In particular the received variable is

always b ound to each time a molecule is received

e

Lemma Let x bethevector of variables fvQ dv J and befresh vari

ables We have

def J Q in P

e e e

def J jhx i Qj hx i in P jhx i

Complex denitions

We compile every complex denition with nway join patterns andor multiple

clauses connected by into several simpler denitions with only one pattern that

joins at most two atoms For that purp ose we implement an invisible layer be

tween the emitters and the guarded pro cesses of the denition that makes explicit

the automaton that matches messages and patterns

For clarity we use the syntactic sugar developp ed for our language to present

our enco ding except use the xhv i notation to indicate asyncronous names rather

than capitalization as in Section We enco de the denition D J P J

n

P Up to conversion we may assume that patterns J joins messages of the

n

k

e

form x hv i Then the translation of def D in Q is

i i

def getjseths vi return s v to get

let s v get

u

def x hu i run seths fig vf gi

i v

i

if i s then run x hv i

i i

let s v get

if s v

k

def p hi then run P jseths s vi

k k k

else run seths vi

run p

k

run p hi

k

run seth i

run Q

The translation consists of a simple twowayjoin denition that matches inter

e e

nal actions to an internal state hs v i that caches the current p ending messages

e

on each of the dened names x of D s represents the set of names of available

i

e

messages and v contains one of the p ending values for these names if any

For each J the auxiliary pro cess denition p rep eatedly checks whether the

k k

current state s contains all the dened variables s of J and triggers the guarded

k k

pro cess P when successful

k

For each x the new denition inserts values of messages in the current state

i

Notice that if another message is already present it is removed and resentonx

i

e

this makes sure that the choice of messages that are present in the cache v can

freely b e reconsidered until they are actually senttoaP

k

Lemma If DQ is the translation dened above then

def D in Q DQ

Hence if P is dened as the jointerm obtained from P by applying the above

translation to al l compound denitions in P then is ful ly abstract

Polyadic messages

As in the calculus wecommunicate tuples of names on auxiliary private names

we rst describ e the proto col for pairs the pro cess O sends the pair u v on

xuv 

t

P extracts a pair u v from a pair name p then executes x the context I

uv 

P On the senders side an internal state w holds the next value to be returned

to rw Again we use the syntactic sugar of the language to hide continuations

def r jw hz i return z to r

run w hui

let z r

def

O

xuv 

def rw run w hv i

return z to rw

run xhrwi

let u t

def

t

let v t

I P

uv 

run P

The translation of wellsorted p olyadic pro cesses is dened inductively on pro

cesses after a rst enco ding of tuples as nested pairs we only have to describ e

the translations for dyadic messages and denitions

def

xhu v i O

xuv 

def xhu v ijy hw z i P in Q

r t

def x r jy tI I P

uv  wz 

r

def xr I O

def

x uv 

uv 

t

O def y tI

y wz 

wz 

run Q

This enco ding may app ear redundant as pairs are enco ded and deco ded

twice However this ensures that only valid pairs are involved in the actual join

denition With only one level of enco dings some contexts that do not comply

with our proto col may interfere as is the case in the following example where

P Q but C P C Q

def

P def xhu v ijy hw z i bhbi in z hxijxha aijy ha ai

def

Q def xhu v ijy hw z i bhbi in z hxijbhbi

def

C def z hxi h def ti in xhti in

Lemma The encoding is ful ly abstract The core monadic and the core

polyadic variants of the joincalculus have the same expressive power

A comparison with the calculus

Despite their syntactic dierences the joincalculus can be considered as an o

spring of the calculus in the asynchronous branch of the family The latter was

intro duced indep endently in as the mini asynchronous calculus and in

as the calculus Both authors suppress the guards on emission and compare the

result to the original calculus Going further in that direction the joincalculus

is an asynchronous calculus with the strong restrictions

the three binders scop e restriction reception replicated reception are syn

tactically merged in a single construct the denition

communication o ccurs only on dened names

for every dened name there is exactly one replicated reception

There are several reasons to b e interested in a formal comparison b etween the

two calculi the calculus has b een thoroughly studied it is a reference calculus

and many results relate other formalisms or implementations to it

Therefore it is app ealing to translate such results automatically to the joincal

culus On the other hand some issues are b est addressed in the joincalculus as

for instance lo cality implementation purp oses and explicit distribution Besides

this also provides a deep insightinto what is common and what is dierentinthe

joincalculus and in the calculus

Both enco dings that are used to get our most precise results are complex

but their underlying ideas are simple In particular much simpler enco dings can

be obtained in less general settings for instance programs written in PICT and

programs in the language presentedinsectionwould use very similar implemen

tation techniques

Using the results of the previous section we consider the recursive polyadic

joincalculus with at most twowayjoin denitions as the target calculus to enco de

the calculus and its monadic variant for the reverse enco ding

We rst recall the denition of the asynchronous calculus then we enco de

the calculus in the joincalculus The rst naive enco ding replaces eachchannel

of the calculus byatwoway denition however some more work is needed to

achieve full abstraction We present our approach based on rewalls in detail

but we defer the presentation of the pro of to annex A In the same manner we

then enco de the joincalculus in the calculus using the straightforward transla

tion of denitions into scop erestriction and replicated reception Using the same

approach we also need to rene the enco ding The sketch of the pro of can be

found in annex B

In all our enco dings we will assume that every name that is intro duced in

the translation rules is a fresh name that do es not app ear elsewhere in the terms

This mayinvolve some conversion

The asynchronous  calculus

To study this relationship we precisely compare the joincalculus to the asyn

chronous calculus Weusethesyntax of Milner in Without loss of general

itywe allow only monadic messages and replicated input instead of more general

recursion

def

P P jQ j uP j xu j xuP j xuP

Following the observational approach of the congruence is

dened for the calculus as the asynchronous barb ed congruence whose barbs

are the emissions on free channels

Theorem The joincalculus and the summationfree asynchronous calculus

have the same expressive power up to their weak outputonly barbed congruences

Asynchrony Relays and Equators

Our enco dings essentially rely on the prop erties of the asynchronous reduction

based calculus as discussed in and on similar prop erties of the join

calculus

In both calculi it is not p ossible to observe the reception of a message for

xu and it is not p ossible either to distinguish instance we have xu

between two dierent names that have the same external b ehaviour We illustrate

the latter with a denition of equators between names

def

M xu yujy v xv

xy

This pro cess rep eatedly receives values from x and forwards them to y and vice

versa so that no matter which name x or y is used to send a value it can always

b e made available for reception on the other name in one internal reduction

Lemma For al l processes P Q

x x

jQ jP M P f g Qf g implies M

y y

xy xy

Enco ding the  calculus

Naive structural denition

Toeachchannel x of the calculus we asso ciate twonamesx for output x for

o i

input and an enclosing denition that matches output and input The emitter

simply sends values on x the receiver denes a name for its continuation and

o

sends it as a reception oer on x

i

def

P jQ P j Q

def

xP def x hv v ijx hi hv v i in P

o o i i o i

def

xv x hv v i

o o i

def

xv P def hv v i P in x hi

o i i

def

xv P def hv v i x hij P in x hi

o i i i

For example we translate the following pro cess and its reduction

x xajxbjxuyu xxajyb

to the joinpro cess and the series of reductions

def x hv v ijx hi hv v i

o o i i o i

in x ha a ijx ha a i

o o i o o i

j def hu u i y hu u i in x hi

o i o o i i

def hu u i y hu u i

o i o o i

in def x hv v ijx hi hv v i

o o i i o i

in x ha a ijy hb b i

o o i o o i

In the same manner any reduction on a b ound name in the calculus can be

simulated by a joinreduction followed by a deterministic reduction in the join

calculus and conversely any reduction in a joincalculus translation b elongs to

one of these two cases and can be simulated in at most one reduction in the

calculus

Full abstraction of the enco ding

Unfortunately the previous enco ding do es not reect the behaviour of pro cesses

of the calculus when placed in an arbitrary joincalculus context the proto col

relies on the presence of sp ecic denitions for every free name while the context

may dene them in some other way

xajxbjxuyu cannot reduce anymore b ecause For example the translation

there is no englobing x Worse xu xu exhibits a barb on x that reveals the

i

presence of an input for x and allows a context to distinguish this pro cess from

And b ecause of mobilityitwould not b e enough to supply a correct denition of

x x for every translated free name since a context would still b e able to forge

o i

a message x hz ti from some of its own names z t with arbitrary denitions

o

To protect the translation from hostile contexts the names resulting from the

free channels of the term must setup a rewall that enforces the proto col

We rene our rst idea eachchannel x is now represented as several pairs x x

o i

from the naive enco ding that cannot b e distinguished from the outside Two pairs

are merged by rep eatedly communicating their p ending messages to one another

New pairs are dened at runtime according to the following secure proto col

Whenever a pair of names is received from the outside the rewall denes

a new correct proxy pair merges it to the external pair and transmits the

new pair instead

Whenever a pair of names is sent to the outside a new rewall is inserted

to set up proxies for future messages on this pair

As a result the translation and the context never exchange names from a syntactic

p oint of view We use the following contexts to build the rewall on top of the

naive translation

def x hv v ijx hi hv v i

def

o i i o i

l

P

x

in def x hv v i phv v x i in

o o i o i

l

def

E P x hx x ij

x x e o i

def

M def px x P hy y ij M in

o i y o i

xy

For every free name x P enco des the creation of a new proxy for its output E

x x

do es the same and also exp orts the proxy on a conventional free name x Finally

e

M recursively denes the proxy creator p for the whole translation

Notation Wheneveracontext dened with a name index app ears without this

index it stands for the application of the context for at least all the free variables in

def

the term and for a denition for p For instance E xy ME E xy

x y

Theorem For al l processes Q R in the calculus

Q R E Q E R

Note that E catches all the free variables of P jQ In the pro of we also givean

auxiliary enco ding that is strictly comp ositional

Enco ding the joincalculus

The reverse translation is simpler b ecause the joincalculus is somehowthe cal

culus with restrictions on communication patterns However a careful enco ding

is needed to prevent contexts of the calculus from reading messages from the

names they receive from the translation

Structural denition

def

QjR Q j R

j j j

def

xhv i xv

j

def

def xhuijy hv i Q in R xyxuy v Q j R

j j j

Reductions in calculus translations corresp ond exactly to the reception of

messages in joinpatterns In the translation we lo ose the symmetry between x

and y and the atomicity of their joinreduction but it do es not matter as scop e

restriction and guarantee that these details cannot b e observed

j

Again the translation reveals to o much ab out the source pro cess as a context

of the calculus could start reading values on names b ound in the translation of

denitions Indeed if wewere translating the joincalculus into an asynchronous

calculus extended with a typ e system with p olarities we could sp ecify write

only typ es for every channel that is communicated inside of the translation and

the typ ed previous enco ding would already b e fullyabstract

Full abstraction

To obtain our second full abstraction result we also need to build a rewall

The interface recursively sets up oneway relays for every name that crosses the

b oundary It is built from the following terms with the same convention on

indices

def

xv v R rv v jyv

e xy e e

def

R rr x x R j

e xx

e

def

j E xR

xx

e x

R is a global denition for the translation which sets up onewayrelays R

xx

e

or R from the rst to the second of its argument When a relay forwards a

xx

j

message it also sets up a relay going in the reverse direction for the transmitted

value There is no syntactic scop e extrusion of the translations of denitions and

their synonym can always receive messages We use the same notation convention

as b efore E P stands for the application of R followed by applications of E

x

j

for at least all free variables of x of P

Theorem For al l processes Q R in the joincalculus

Q R E Q E R

j j

Future work

Many interesting issues on the joincalculus are outside the scop e of this pap er

They include actual implementation techniques typ e systems and in particular lin

ear typ es for the names that representcontinuations as in extensions

of the calculus with records for a b etter supp ort of ob jectoriented programming

Observation and equivalences also deserve a more detailed treatment as well as a

comparison with their counterparts in the asynchronous calculus

To conclude we briey mention our current usage of the reexive CHAM

and of the joincalculus in a programming language design where resources and

environments are explicitly distributed while the details of the network and its

connectivity remain hidden In a practical distributed setting where some sites

may fail the atomicity of each interaction must be sp ecied accurately in a

way that can b e implemented lo cally The joincalculus relieves us of many di

cult issues As synchronization can only happ en on denitions it is sucient to

require each denition to be annotated with some lo cation that is shared by all

its names and guarded pro cesses Likewise the actual allo cation of resources for

a denition such as waiting queues automaton and closures happ ens lo cally as

the denition is activated using the chemical rule strdef In that setting mes

sages are forwarded to their denition asynchronously then handled lo cally We

currently study extensions of the reexive CHAM and of the language that pro

vide explicit control of the lo calization of denitions on several sites and p ossibly

their imp erative migration from one site to another This would make intensive

interaction more lo cal and would protect it from lo cal failure A distributed

prototyp e is under way to assess the feasibility and the interest of a distributed

implementation of pro cess calculi

Acknowledgments

This works started from a seminar on distributing the calculus held in

at INRIA with the participation of Damien Doligez Florent Guillaume Jean

Jacques Levy Luc Maranget and Didier Remy We also thank Rob erto Ama

dio Gerard Boudol Xavier Leroy Benjamin Pierce Davide Sangiorgi and David

Turner for fruitful discussions and comments We used Paul Taylors macros for

typ esetting diagrams

References

G Agha I Mason S Smith and C Talcott A foundation for actor compu

tation Technical rep ort UIUC

G A Agha Actors a Model of Concurrent Computation in Distributed

Systems MIT Press Cambridge MA

R Amadio and S Prasad Lo calities and failures Foundations of

Technology and Theoretical Science

JM Andreoli and R Pareschi Communication as fair distribution of knowl

edge In Proceedings OOPSLA ACM SIGPLAN Notices pages

Nov Published as Pro ceedings OOPSLA ACM SIGPLAN Notices

volume numb er

JP Banatre M Banatre and F Ployette Distributed system structuring

using multifunctions Rapp ort de Recherche INRIA Rennes June

G Berry and G Boudol The chemical abstract machine Theoretical Com

puter Science

G Boudol Asynchrony and the calculus note Rapp ort de Recherche

INRIA SophiaAntip olis

L Cardelli A language with distributed scop e Systems

Jan A preliminary version app eared in Pro ceedings of the nd

ACM Symp osium on Principles of Programming Languages

A Giacalone P Mishra and S Prasad FACILE A symmetric integration

of concurrent and functional programming International Journal of Paral lel

Programming Also in TAPSOFT ed J Diaz and

F Orejas pp SpringerVerlag Lecture Notes in

K Honda and M Tokoro An ob ject calculus for asynchronous communi

cation In P America editor Proceedings ECOOP LNCS pages

Geneva Switzerland July SpringerVerlag

K Honda and M Tokoro On asynchronous communication semantics In

P W M Tokoro and O Nierstrasz editors Proceedings of the ECOOP

Workshop on ObjectBased LNCS pages

SpringerVerlag

K Honda and N Yoshida On reductionbased pro cess semantics Founda

tions of Software Technology and Theoretical Computer Science

K Honda and N Yoshida Combinatory representation of mobile pro cesses

In Proceedings POPL

N Kobayashi B C Pierce and D N Turner Linearity and the picalculus

In Proceedings POPL

L Maranget Twotechniques for compiling lazy pattern matching Research

rep ort INRIA

R Milner Communication and Concurrency Prentice Hall New York

R Milner Functions as pro cesses In Automata Languages and Program

ming th Int Col l volume of LNCS pages Springer Verlag

July

R Milner The polyadic calculus a tutorial In F L Bauer W Brauer

and H Schwichtenberg editors Logic and Algebra of Specication Springer

Verlag

R Milner J Parrow and D Walker A calculus of mobile pro cesses parts I

and I I Information and Computation pages Sept

R Milner and D Sangiorgi Barb ed bisimulation In Proceedings ICALP

LNCS pages Vienna SpringerVerlag

B C Pierce D Remy and D N Turner Atyp ed higherorder programming

language based on the picalculus In Workshop on and its

Application to Computer Systems Kyoto University July

B C Pierce and D Sangiorgi Typing and subtyping for mobile pro cesses

Mathematical Structures in Computer Science To app ear A summary

was presented at LICS

B C Pierce and D N Turner Concurrent ob jects in a pro cess calculus In

T Ito and A Yonezawa editors Theory and Practice of Paral lel Program

ming TPPP Sendai Japan Nov number in Lecture Notes in

Computer Science pages SpringerVerlag Apr

B C Pierce and D N Turner Pict A programming language based on the

picalculus Technical rep ort in preparation

D Sangiorgi and R Milner The problem of weak bisimulation up to

In W R Cleaveland editor Proceedings of CONCUR LNCS pages

SpringerVerlag

G Smolka A foundation for higherorder concurrent constraint program

ming In JP Jouannaud editor st International Conference on Con

straints in Computational Logics Lecture Notes in Computer Science vol

pages Munchen Germany Sept SpringerVerlag

D N Turner The calculus Types polymorphism and implementation

PhD thesis LFCS University of Edinburgh In preparation

D Walker Ob jects in the picalculus Information and Computation

A Sketch of the pro ofs of section

Notation In all the diagrams that follow we use the usual conventions for all

relations on plain lines there exists relations on dotted lines and stars denotes

the reexivetransitive closure of a relation

A E is fullyabstract

A Combining translations and contexts

We rst prove the direct implication by studying how a translation can inter

act with an arbitrary joincalculus context This is p erformed on an auxiliary

translation that is very similar to

Denition The translation maps processes to joinprocesses using the

same structural denition that for except for scoperestriction so that output

always leads to the creation of a new proxy pair and for unguarded outputs where

the denition of x is unfolded

o

def

xP P P

x

h i

def

xv P x hz z ij M when unguarded

z o i

l

zv

Denition Hybrid terms are terms of the joincalculus that are structural ly

equivalent to some P E j Q where E is a joincalculus process Q is a calculus

process and P is an header of denitions such that for al l free names x in Q P

x

appears in P and such that every message on x channels matches some x hv v i

o i

l l

where P appears in P

v

In particular the pro cesses E Q that app ear in the theorem are hybrid

terms Wenow study reductions inside of hybrid terms These reductions can b e

reductions that use the joindenition of some x x which corresp ond to

i

l

reductions in the calculus

reductions that manipulate pairs of synonyms or trigger continuations

which are induced by the enco ding

reductions inside of E which are indep endent of the translation

We are mostly interested in the rst family of reductions To get rid of the

details of the enco ding we rst dene two auxiliary expansions to relate hybrid

terms that dier only b ecause some deterministic reduction hasnt b een p erformed

yet or b ecause some extra synonyms havebeenintro duced for pairs x x Then

o i

we use the weak bisimulation upto expansion technique

Lemma Let be the relation on joinprocesses that contains al l pairs of

det

def def

deterministic reductions Then is a barbedexpan

det det det

det

det

sion

Lemma Let relates hybrid terms with one additional pair of synonyms

merge

on the lefthandside

h i

x

PP E j Qj M PP E j Q f g

xy merge x y

xy

def

merge

merge

Then is a barbed expansion

merge

Lemma E Q E Q

Lemma The reductions in the calculus can be mimickedontheirtranslations

if Q Q then P Q P Q

det merge

Lemma For al l pair of hybrid terms P E j Q P E j R

if Q R then P E j Q P E j R

Pro of Let the relation B contains all the pairs of hybrid terms that are obtained

from congruent pro cesses

Q R P E j Q B P E j R

We establish that B To this end we distinguish among the reactions

that may happ en on the lefthandside hybrid term and in each case simulate it

on the righthandside We consider four cases

Reduction outside of the translation they are the same on b oth sides

Reduction inside of the translation a communication o ccurs between a re

ception oer and an output it corresp onds to a communication in the original

term except that as the value is received a new proxy is created and that

several deterministic reductions may be necessary to reach an hybrid term On

the right side we use Q R to obtain a sequence of reductions R R and

we mimic them in the translation

B

P E j Q P E j R

B

P E j Q P E j R

Intrusion of a pair of channels from the environmentinto the translation The

e

receiving term Q is of the form uQ jxz Q while there is a correct p ending

value x hz z i in the joincalculus and a denition to match them We rst use

o i

l

an auxiliary commutative diagram to push the emission under the translation

Using our lemma we can then build reductions for the right term and with a

few deterministic reductions on the b ottom left we get a new pair in B On b oth

sides we use our expansions on hybrid terms to switch x hz z i and xz

o i

l

e

xz j uQ jxz Q xz jR

e

R uQ jQ

B

P E jx hz z ij R P E jx hz z ij Q

o i o i

l l

B

e

P E j uQ jQ

Extrusion of a pair of channels from the translation to the environment the

emitting term is of the form Q uQ jxy where p ossibly u y If l u are

fresh names we get a similar emission for R by applying the congruence Q R

def

lujxy l uM j to the context O

yz

O uQ j xy O R

uQ jM u R jM

yz y z

In the diagram the reductions on the right can b e reordered as internal reductions

in R followed bythetwo reductions on x l with O From the rst ones we build

the corresp onding reductions from the translation on the right to a term that is

an expansion of u R jM

y z

B

P E x hi j R P E x hi j uQ j xy

i i

h i

B

P E hz z i juQ jM

o i

yz

From the previous diagrams and as B is a congruence and resp ects the

barbs we obtain by denition of that B and in particular B



A Correctness

We need yet another translation that is fully comp ositional each term is wrapp ed

in a protective context at each step of the structural denition conversely the

names of each subterm must b e made synonym for the names in the current term

Denition The translation maps processes to joincalculus processes

def

P jQ E I P jI Q

def

xP N P

x

def

xv E x hv v i

o o i

def

xv P E def hv v i I P in x hi

o i i

def

xv P E def hv v i x hijI P in x hi

o i i i

with the fol lowing denitions and with the convention on indices

def

in I def x hy y i M

x e o i

xy

def

N def x hy y i in

x e o i

I catches exp orted synonyms for channels in the scop e of the context N

prevents extension thus providing lo cality

Lemma Q Q E Q

Pro of In each case of the structural induction we use variants of the relation

E I E P E P We presenttwo signicant cases

x x x det merge x

def

P jQ E I P jI Q

E IE P jI E Q

E P jQ

def

xP N P

x

EN E P

x x

EP P

x

E xP



Lemma if E Q ER then Q R

Pro of fQ R E Q E R g is a barb ed congruence in the calculus The

congruence follows from the previous result and the congruence prop ertyof

E C Q C Q C Q C E Q

The asynchronous barbs are the same They can be individually tested in

simple contexts The bisimulation is obtained from previous lemmas 

A E is fullyabstract

j

In this part weuseconventions for names In the calculus z is a free variable

j

of the translation that corresp onds to the external name z In the joincalculus

b

we intro duce for each name x another name x that may app ear at most once

b

in a pro cess and only as the port name of an unguarded message xy we note

b

P a pro cess that may contain these messages Such messages will keep track of

internal names y that have b een exp orted to the context to this end we adapt

to translate them into incoming relays

j

def

b

R xy

xy

j

j

Denition A hybrid term is a term of the calculus that is structural ly equiv

alent to

h i

b

P C E

z

j

b

e

where C is any context of the calculusof the form w R j and where P is a

g

b

xx such that its free vari joinprocess with possibly some unguarded messages

e

e b

ables are in fz xg

j

Lemma

h i h i

x

j

b b

C x y R jR j P C z R j P f g

j j x z y z j x z y

j j j j

j j

Lemma Let be the largest expansion between the calculus and the join

J

calculus that respects barbs Then for al l joinprocess P we have P P

J

j

Lemma The relation that contains al l pairs of hybrid terms whose extended

joinprocesses are congruent is a barbed congruence in the calculus

Pro of The congruence prop erty is obvious the bisimulation requires a case

analysis which will also establishes that barbs are preserved We study in more

details the interactions between the translation and its context and the setup

of new relays Four kinds of reductions mayoccur

External communication apply the same one on the other side

Intrusion of an external message is received on an incoming relay the messages

is withdrawn from the calculus context and committed to an internal usage

except from the rst step which prevents the input of the message in the context

the following steps are deterministic and lead to a new hybrid term

h i h i

b b

b b

C xujE P x x C E P xhuijx x

z uz

det

j j

To obtain a bisimilar hybrid term on the other side we use the joincalculus

context

def

b b b b

O def y x xx in def xx xhuijy x in

i

b

Both joinpro cesses have a barb on x that is necessarily a single unguarded mes

b

sage Consuming x on b oth sides leads to a pair of congruent pro cesses We then

b

discard the useless denition of xx and wrap b oth pro cesses as a new pair of

related hybrid terms

Internal reduction on the translation of a denition using in the joincal

culus we obtain a sequence of reductions on the left side and mimic it in the

translation Some deterministic reductions may b e needed on b oth sides to reach

ahybrid term

Extrusion by internal reduction on an exp ort relay in a few deterministic re

ductions messages on translations of free variables are exp orted to their public

calculus name

i h i h

b b

b

zxjE P xx C E P z hxi C x

z z

det

j j

We use the following context O to obtain an adequate sequence of reductions

e

on the right side the rst emission on z is handled in a sp ecial way while the

j

next ones are silently transmitted

def e in def ahuijl hi uhi

in def z hxi zhxi

def

O in def z hxijchi hxijchz i

e

b

in def hxi xxjahei

in ch ijahdijl hi

h h i i

b b

Q P z hxi O O

e e

b

b

b

P xu Q

c

Q has no barb on c we can reorder the reductions on the right to defer

interaction with the context O to obtain a sequence of reductions to mimic in

e

the translation 

Lemma for al l P Q in the joincalculus

P Q E P E Q

j j

Denition We use the compositional encoding where D xhuijy hv i Q

j

to obtain the second half of the theorem

def

QjR Q j R

j j j

def

x v xhv i E

j j

xv

j

def

def D in R xyxuy v Q j R

j j j

e

Lemma For every joinprocess Q with free variables z

Q E Q

z

j j

We conclude using the same argument that for the reverse translation