Checking bisimilarity for finitary π-calculus - CiteSeerX

0 downloads 0 Views 874KB Size Report
Abstract. In this paper we associate to every z-calculus agent an it- ... While very convenient in practice, partition refinement algorithms are not presently .... P ::=O ] a.P ] PIlP2 ] PI + P2 ] (vx)P I [x= Y]P ] A(xl,...,Xr(A)) where the .... ab [{a,b}[ 0 a(b) {a} ..... we describe the time complexity of the bisimilarity test for two ~r-automata.
Checking Bisimilarity for Finitary 1r-calculus* Ugo Montanari and Marco Pistore Computer Science Department, University of Pisa Corso Italia 40, 56100 Pisa, Italy {ugo,pistore} ~di.unipi.it

A b s t r a c t . In this paper we associate to every z-calculus agent an itredundant unfolding, i.e., a labeled transition system equipped with the ordinary notion of strong bisimilarity, so that agents are mapped into strongly bisimilar unfoldings if and only if they are early strongly bisimilar. For a class of finitary agents (that strictly contains the finite control agents) without matching, the corresponding unfoldings are finite and can be built efficiently. The main consequence of the results presented in the paper is that the irredundant unfolding can be constructed also for a single agent, and then a minimal realization can be derived from it employing the ordinary partition refinement algorithm. Instead, according to previous results only pairs of r-calculus agents could be unfolded and tested for bisimilarity, and no minimization of a single agent was possible. Another consequence is the improvement of the complexity bound for checking bisimilarity of finitary agents without matching.

1

Introduction

Process description languages (the most studied of them is Milner CCS [11]) are useful for specifying and studying concurrent distributed systems. They are equipped with well-developed operational and abstract semantics, and program verification has been an issue in their design from the very beginning. In the finite state case, efficient and practical techniques and tools for verification have been developed [7, 10], and they are actually used in several application fields, e.g. in protocol and hardware design. Finite state verification is successful here, differently than in ordinary programming, since the control part and the data part of protocols and hardware components can be often cleanly separated, and the control part is usually both quite complex and finite state. One of the most important checks in finite state verification is for bisimilarity. The most used algorithm for this check is a variant of Paige and Tarjan partition refinement algorithm [9, 15]. As for language equivalence of finite state automata, the algorithm checking for bisimilarity can produce at the end a minimal realization, which is often dramatically smaller than the state space of the given agent. Theoretical results make sure that the minimal realization can replace * Work supported in part by Esprit Basic Research project CONFER and by Progetto Speciale CNR ~Specifica ad Alto Livello e Verifica Formale di Sistemi Digitali'.

43 the original agent in all subsequent checks, at least for properties expressible in the associated Hennessy-Milner logic. While very convenient in practice, partition refinement algorithms are not presently available for all process description languages. In fact in some cases the observations labeling the transitions of agents are history dependent, i.e., they may refer to observations occurring in previous transitions of the same agent. This is the case for instance for CCS with causality [4], where a visible transition exhibits, in addition to an action, also pointers to the transitions in the past it is caused from. A similar case is CCS with localities [1]. For history dependent agents, bisimilarity can presently be checked at two prices. The first is that the agents must remember the names of the past transitions they can possibly refer to in the future. This extra information tends to make the number of states infinite (if all the past transitions are remembered) but if the sizes of the agents involved in all the computations are bounded, it is possible to see that only a bounded number of past transitions must be stored. The second price is that the algorithm checking for bisimilarity, called on the fly [5, 2], requires the contemporary generation of the state spaces of both agents to be checked, and consequently it does not produce a minimal realization. Another, quite interesting case of history dependent process description language is the r-calculus [13, 12]. It has the ability of sending channel names as messages and thus to dynamically reconfigurate agent acquaintances. More importantly, 1r-calculus names can model objects (in the sense of object oriented programming) and name sending thus models higher order communication. New names can be created at run time and referred to in subsequent input or output operations. It is thus evident the history dependent character of ~r-calculus. Owing to the nature of input and bound output It-calculus transitions, also very simple agents do not exhibit a finite state behaviour; other finiteness requirements are more significant in this context. Particularly interesting is the class of finitary agents: an agent is finitary if there is a bound to the number of parallel components of all the agents derivable from it. This is a very liberal notion, but it does not correspond to a syntactical class of agents. A syntactical but more restrictive notion is that of finite control agents, i.e., the agents without parallel composition inside recursion. Three kinds of bisimulation equivalences are relevant for r-calculus: early and late bisimilarity (introduced by Milner, Parrow and Walker in the first 1rcalculus paper [13]), and open bisimilarity (introduced by Sangiorgi [16]). An algorithm for checking open bisimilarity of finitary agents that follows the on the fly style has been included in the Mobility Workbench [19]. For early and late bisimilarity, decidability of equivalence is proved in [3], where it is shown that for every pair of finite control agents only a finite number of names is sufficient. Once the number of names is guessed, the state spaces of both agents can be built, and the efficient partition refinement algorithm can be applied. However, the number of names which is needed depends on both agents, and thus no state space of a single agent can be build, let alone reduced to a minimal realization. In fact, if the matching agent is left unspecified, the only

44 possibility is to take an infinite number of names, and an infinitebranching (and thus infinite) transition system is obtained. Moreover the ghess of the number of names works only for the finite control agents and is not extendible to all the finitary agents. In this paper we show another approach for checking (early strongly) bisimilarity. W e show that, by suitably choosing the object name, it is possible to consider only one bound output transition. Similarly, by using as object names the names already in the agent plus one new name, only a finite number of input transitions is needed. The interesting point is how to choose these object names so that bisimilar agents will do the same choices of names: for a bound output, for instance, it is not possible to simply choose the firstfresh n a m e (i.e.,the first n a m e which does not occur free in the agent), since there are bisimilar agents with different sets of free names. Our proposal is based on the following notion of active names2: a n a m e x is active for P if (vx)P is not bisimilar to P (with (ux)P we represent agent P where name x has been restricted). T w o bisimilar agents have the same sets of active names; moreover, ifwe restrict an agent P with respect to all its nonactive names we obtain a bisimilar agent 4~P, whose free names are all active. After this restriction, the first fresh n a m e can be safely chosen for a bound output. Given an agent P we define its irredundant unfolding as the following labeled transition system: consider all the transitions of ~LP in the ordinary early transition system and discard i) all the bound output transitions that extrude a name different from the first fresh (nonactive) name in ~ P and ii) all the input transitions that receive a value not already active in g P , except for the first nonactive one; for each remaining transition 4~P ~ , P~, the transition ~P~ ~ ~ P ~ is added to the irredundant unfolding and the construction continues from ~tP ~. The first result we obtain holds for all the agents: two 7r-calculus agents are early bisimilar iff their irredundant unfoldings are bisimilar. Moreover, if an agent is finitary, the corresponding irredundant unfolding is finite: to decide whether two finitary agents are bisimilar we could build the corresponding unfoldings and then use the standard partition refinement algorithm for checking their bisimilarity. To construct the irredundant unfoldings, however, the active names of the agents reached in the construction have to be computed. In the fragment of Itcalculus without matching an efficient algorithm carl be used to this purpose: in this case the active names of an agent can be computed by considering the names appearing in the labels of the computations of the agent. We also introduce a very compact structure (called r-automaton) that represents all the possible computations of an agent and that contains all the information for computing the active names and for generating the irredundant unfolding. With this algorithm the bisimilarity of two finite control agents can be checked with a worst-case running time of 2 ~176 where k is the syntac2 The idea of active names used here is strongly related to the idea of used n a m e s introduced in [8] for constructing finite state transition systems for agents of a CCS with value passing.

45 tical size of the agents. This improves the t i m e complexity mentioned in [3] for the s a m e purpose, which is 2 ~ log k). Moreover, our approach should improve over [3] even more in the average case t h a n i n t h e worst case. 2

Background

2.1

Labeled Transition Systems (lts)

A labeled transition system (Its) is a tuple (Q, q0,s -

_

-

-

Q is a set of states; q0 E Q is the initial state; s is a set of labels; : -~C Q • s • Q is a set of

,), where:

transitions.

I f ( a , l , a ~) E~ , we write in briefa~ I a ~. We use different arrow symbols to distinguish between different lts. Given two Its A = (QA, q~ and S = (QB, q~163 ~--+), a relation 7~ C QA x QB is a simulation iff:

aT~b and a t ~a ~, there exists some b, t ~U such t h a t aeT~U.

- whenever

A relation 7~ C The two Its are

QA x QB is a bisimulation iff b o t h T~ and Tr -1 are simulations. bisimilar (A B) iff qA~qB 0 0 for some bisimulation R .

2.2

s

I

t

-

c

a

l

c

u

l

u

The z'-calculus we present here is early and monadic; it was first introduced in [14], but we present a slightly simplified version, following in part the style proposed in [18] for the polyadic 7r-calculus. Given a countable infinite set of names .Af (denoted by a , . . . , z ) , the ~rcalculus agents over .Af are defined by the syntax:

P ::=O ] a.P ] PIlP2 ] PI + P2 ] (vx)P I [x= Y]P ] A(xl,...,Xr(A)) where the

prefixes a are defined by the syntax:

. ::= I I x(u), and r(A) is the range of the agent identifier A. The occurrences of y in x(y).P and (~y)P are bound; free names are defined as usual and we indicate t h e m with fn(P). For each identifier A there is a definition A(yl,..., Yr(A))de_fp (with Yi all distinct and fn(P) C {Yl... Yr(A)}) and we assume t h a t each agent identifier in P is in the scope of a prefix (guarded recursion). If a : AF --~ Af, we denote with P a the agent P whose free names have been replaced according to substitution a (possibly with changes in the bound names); we denote with { y l / x l . . . yn/xn} the substitution that m a p s xi into Yi for i = 1 , . . . , n and which is the identity on the other names. We define v-calculus agents up to a structural congruence - defined as follows:

46 agents which differ by a-conversion are identified; + is associative and commutative and 0 is its identity; [ is associative and commutative and 0 is its identity; [x=x]P-Pand[x=y]0=0; (vx)0 = 0 and ( v x ) ( v y ) P = ( v y ) ( v x ) P ; - if x ~ f n ( P ) then ( v x ) ( P I Q ) =_ P l ( v x ) Q . -

-

-

-

-

The actions an agent can perform are defined by the following syntax: ::=

I

l Cz) l

x and y are free names o f p (fn(l~)), whereas z is a bound name (bn(p)); n(p) =

/ n ( , ) u bn(p). The transitions for the early operational semantics are defined by the axiom schemata and the inference rules of Table 1.

Table I. Early operational semantics. OUT ~y.P ~9~ Y P

TAU r . P _L. p SUM

PI - ~ P ' pa + p2 ~--~p '

PAR

COM PI ~--LYP~ P2 *Y,P~

P~ if bn(l~) n fn(P2) = 0 pllpP1 ~~__~p~lp2

CLOSE /)1 ~

PIIP2 ---~ ~ P~IP~ ' ' RES

P ~

P'

(vx)P ~--~(vx)P'

IN x(y).P ~x z P{z/y}

if x r n(#) OPEN

P~

P2 *Y, B'2 if v ~ f n ( P , )

P ~y' P' if x ~ y, z r fn((vy)P') (vy)P ~ P'{z/y}

IDE P { y , /Ax(,y, ., ., .. ,. . , Y~(A)/Xr(A)} Y~(A)) ~ P'~

P' if A ( x l , . . . , Xr(A)) de___fp

A relation 7~ over agents is an early simulation iff, given PTiQ: - whenever P

~, P ' with bn(p) N f n ( P ,

O) =

0, then Q ~

Q' and P'7~O'.

A relation 7~ is an early bisimulation iff both :R and 7~-1 are early simulations. Two agents P and Q are early bisimilar (P .~ Q) iff PT~Q for some early bisimulation 7~.

3

From Agents to Unfoldings

It is easy to notice that, when checking the early bisimilarity of two agents, not all the names have to be considered as values of input transitions: only the names free in the agents plus one fresh name are required. Similarly, just one fresh name is required in the bound outputs.

47 This observation can lead to a naive construction that eliminates the infinite branching: let us consider the free names of the agent P (we call them syntactically active names). In constructing the state space of an agent, we then introduce at any time only one bound output transition, employing as object the first name not syntactically active, and as many input transitions as there are syntactically active names, plus again the first name not syntactically active. We call this transition system the syntactical unfolding of P . The conjecture that two agents are early bisimilar iff their syntactical unfoldings are bisimilar (according to the usual notion of bisimulation on ordinary labeled transition systems) is clearly false. Let us consider for instance the following agents: P = x(y).O and Q = P + (vw)(vz. Agents P and Q are bisimilar (the extra summand in Q is deadlocked), but their syntactical unfoldings are not: agent Q has z as a syntactically active name, and thus it is able to execute a transition labeled by xz, while P cannot. From the above example it is clear that considering syntactically active names is inadequate, since bisimilar agents can have different sets of free names. We propose the following notion of semantically active or simply active name in P, based on the idea that if (t~x)P is bisimilar to P then x does not play any active role in P . D e f i n i t i o n l . A name a is active for an agent P iff P # (t~a)P; an(P) = {a I P # ( v a ) P } is the set of active names for the agent P . Proposition2.

If P N p ' then an(P) = an(P').

In addition, we define the irredundant closure g P of P as the restriction of P with respect to all its nonactive names. D e f i n i t i o n 3 . Given an agent P , its irredundant closure is the agent JJP = ( u a l ) - - " (uan)P, where { a l , . . . , an} = f n ( P ) - a n ( P ) . An agent P is irredundant if P = ~ P (i.e., if f n ( P ) = an(P)). Proposition4.

P ,~ ~P for each agent P.

Given an agent P , we define its irredundant unfolding in a similar fashion as the syntactical unfolding described above, getting however as states the irredundant closures of the agents instead of just the agents themselves. Since an agent and its irredundant closure are bisimilar, there is no problem if we apply a closure operation at each step of the construction of the state space of the agent. Moreover, in t h i s way we are sure that bisimilar agents will agree in the choice of names for the input and extrusion transitions. D e f i n i t i o n 5 . The irredundant unfolding of an agent P0 is the Its irr-unj~Po) with ~P0 as initial state (gP0 = q0 E Q) and such that whenever P E Q then: - ifP *,Pithen~Lp IEQandP: r;~pI; - i f P *Y, P~ then ~P~ E Q and P ~ P ~ ;

48 if P ~(Y! P ' and y = rain{At f n ( P ) } then ~ P ' 9 Q and P ~(Y/~P'; - i f P - - ~ * P ' and y E t a ( P ) then ~P' 9 Q and p Xy~p,;

-

-

-

if P xv p , and y = m i n { A / - f n ( P ) } then ~LP' 9 Q and P,~(Vl~P'.

If in the previous definition we do not apply the irredundant closure operator to the initial state and to the targets of the transitions (i.e., if we replace g P ' simply with P ' ) we obtain a different Its, called the syntactical unfolding of the agent P0 and denoted syn-unf(Po) (its transitions are represented b y , ,,). In the unfoldings the input of n a m e y f r o m channel x is represented with x(y) if y is new for the agent, with xy otherwise; this expedient, needed in the proof of the following theorem, makes the input labels more similar to the output labels, where we distinguish in a similar way the bound outputs f r o m the free outputs. Theorem6.

Let Po and Qo be It-calculus agents; then Po "~ Q0 iff irr-un](Po) .-~

irr-~n1( Qo ). Proof (Sketch). For ===~: the restriction of the x-calculus bisimilarity relation ..~ to the states of irr-un](Po) and irr-unJ~Qo) yields a bisimulation relation for the two Its. For r a bisimulation ~ for irr-un](Po) and irr-unJ[Qo) yields an early bisimulation up to ~ and up to injective substitution on agents, i.e., if PT~O and P ~, P' (bn(p) N fn(P, Q) = 0) then Q " , Q' and P'a ..~ n .~ Q'a for some injective substitution ~. By the results in [17], PT~Q, implies P ~ Q; since ~PoT~Q,o, we can conclude that P0 "~ ~P0 "~ ~tQ0 "~ Q0[] The previous theorem shows the full correspondence between bisimulations over agents and over their irredundant unfoldings. Therefore the latter can be used to check for the bisimilarity of the starting agents (using the standard partition refinement algorithms); however, the construction of the irredundant unfolding requires to identify the active names of agents and the definition of active names is given in terms of bisimilarity of agents. To break this circle, we give now a different characterization of the active names, t h a t is correct only for 1r-calculus without matching. Assume t h a t an agent P can perform the transition P ~' ~pi; if x appears in it as the channel of the communication or as the object of a free output, it is necessarily active for P; these names can also be seen as those playing an active role in the transition. D e f i n i t i o n 7. The active names an(#) and the inactive names ~-ff(it) of a transition labeled by it are defined in Table 2. Let us consider again the transition P u ~PI. If a n a m e is active in P~ then either it was active also in P or the transition has done it active; in the latter case the n a m e must be the object of an extrusion or of an input; so, if a n a m e is active in P ' and does not appear in it as inactive name, it is active in P too. Summarizing, if P u p , and z 9 an(It) or z 9 an(P') fi-ri(It), then x 9 an(P). The inverse is not true in general, as the following example shows. N a m e -

49 Table 2. Active names of transitions.

It an ~'ff r r r ab [{a,b}[ 0 a(b) {a} {b}

~b {a} I{b} ~(b) {a)I{b}

z is active for P = x(y).[y = z]~x, since P 7~ ( v z ) P (agent ( t , z ) P cannot do the computation xz ) ** )); however, if we consider all the possible transitions P -~?-~[v = z]~z, we see that z q~ an([v = z]~x) and z ~ a n ( z v ) for all v 9 Af. The two rules described before, however, are sufficient to capture all the active names of an agent without matching. P r o p o s i t i o n 8 . A name ~ is active for an agent P without matching iff there is some transition e ~, P ' such that x 9 an(g) or x 9 a n ( P ' ) - ~-ff(p). This proposition still holds if we consider the transitions, , of the syntactical unfolding or the transitions ~ ~ of the irredundant unfolding of P instead of the ~r-calculus transitions ~. In spite of the alternative characterization presented above, in the ~r-calculus (with or without matching) it is not decidable what names are active for an agent. Proposition9.

It is undecidable whether P .~ ( v z ) P .

Proof (Sketch). If we could effectively decide whether P ~ (t,x)P, we could effectively decide the halting problem for Turing machines, too. In fact, for every Turing machine (and starting tape) we can build a ~r-calculus agent T that simulates this machine: every step in the machine corresponds to a fixed number of ~- actions and the agent can perform the action 6o iff the machine is in a halting state. So the machine can halt iff the action ~o can appear in some computation of T; if this happens then T 7~ (~/o)T, whereas T ~ (t/o)T if the output cannot be reached. [] We conclude this section noticing that the idea of active names is not original: in [8] an algorithm is presented for checking bisimilarity in the context of CCS with value passing, i.e., a version of CCS where values can be received and sent during the communications, but where no operations can be done on these values. In this case the transition system is kept finite branching by considering the input of just a symbolic name instead of all the (possibly infinite) values. The chosen name is the first unused one, where a name is unused for an agent if it is not possible for the agent to send it out before receiving it in an input: this is very similar to the alternative characterization of the active names of

50 Proposition 8. Also in this case the standard partition refinement algorithm can be used and a minimal realization can be obtained. The richer context of r-calculus forces to deal also with bound outputs and to consider not only a fresh n a m e for the inputs, but also the active ones. A difference of our approach is t h a t in Definition 1 we give a characterization of active names, which seems to be rather interesting and more general t h a n the one based on the n a m e s appearing in the transitions. In the next section, moreover, we present an efficient algorithm for computing the active names and constructing the unfolding, based on the r - a u t o m a t a , which is not present in [8] (although it can also be applied in that context).

4

Effective C o n s t r u c t i o n of the Irredundant U n f o l d i n g

In this section we show how to construct effectively and efficiently the irredundant unfolding of a finitary agent without matching. We begin with the formal definition of the finitary agents. Definitionl0. follows:

The degree ofparaUelism of the agent P , par(P), is defined as

par(O) = 0 par( o~.P ) = 1 par( Pl lP2 ) -'- par(P1) q- par(P2) par(P1 + P2) = max(par(P1), par(P2)) par((vx)P) = par(P) par(Ix = y]P) = p a r ( P ) par(A(xl, . . ., Xr(A))) = p a r ( P { z l / y l , . . . , Zr(A)/Yr(A)}) if A ( y l , . . . Y~(A)) d e.fp. An agent is finitary if the degree of parallelism of all the agents reachable f r o m it is bound. Function par describes the n u m b e r of parallel components t h a t are present in the agent; if the degree of parallelism can grow with no limits in some computation of an agent, it is obvious t h a t we cannot hope to represent such an agent with a finite lts 3. The following theorem shows t h a t (when quotienting with respect to the structural axioms of r-calculus) the unfolding of a finitary agent (with or without matching) is finite.

Given an agent P, its syntactical unfolding syn-unf(P) and its irredundant unfolding irr-unj~P) are finite iff P is finitary.

Theorem ll.

a It might be possible to give slightly more comprehensive definitions capturing agents with an unbound number of deadlocked parallel components, like P --- ~x.P[(vy)gx. However we cannot see how to do it in a systematic way.

51

Proof (Sketch). It is obvious t h a t ff P is not finitary the unfolding cannot be finite. For the other implication: each parallel component of an agent reachable from P has to appear, up to name substitutions and restrictions, in P or in a definition used by P , so the number of "types" of parallel components is finite; since the number of components is bound by hypothesis, also the reachable agents are finite, up to the usage of names. Finally, since in each of these there is only a bound number of name occurrences, only a finite subset of Af is used in the unfolding. Also the possibility t h a t the recursive definitions generate an unbound number of new restrictions is not a problem, since ( v x ) P = P if x q! f n ( P ) and so all but a bound number of restrictions can be erased using structural axioms. This assures that the unfolding is finite. [] Notice t h a t in general it is not decidable whether an agent is finitary: otherwise it would be decidable whether an agent is finite (i.e., when the agent is finitary and the corresponding unfolding has no cycles), which is instead undecidable. However, there is an important class of finitary agents which can be characterized syntactically: the agents with finite control, i.e., the agents without recursive definitions containing parallel composition. In this case, after an initialization phase during which a finite set of processes acting in parallel is created, no new processes can be generated. To have an algorithm that works for all the finitary agents is important, because possibly there are less restrictive syntactical conditions that, while permitting the creation of new processes also after the initialization phase, still assure a bounded degree of parallelism in all the reachable agents. Further work has to be done in this sense. We can now sketch a first algorithm for constructing the irredundant unfolding of a finitary agent without matching. It first builds the syntactical unfolding corresponding to the agent (which is finite according to Theorem 11) and then determines the active names of all its states, using Proposition 8. The irredundant unfolding can then be built using these informations. In fact, the states of the irredundant unfolding have the form ~t(Q~), where Q is a state of the syntactical unfolding and tr is an injective substitution. The following proposition shows that the active names of Qtr can be deduced from the active names of Q and so the irredundant closure ~(Qcr) can be effectively built. P r o p o s i t i o n 12. /fcr : f n ( P ) --* .hf is an injective substitution, then an(Per) =

~(an(P)). The role of the syntactical unfolding is now only of discovering the active names. However building the syntactical unfolding would be the bottleneck of the whole construction, since its size is usually significantly bigger than the irredundant unfolding. Exploiting the previous proposition, we can construct a more compact structure (we call it 1r-automaton) that merges all the states of the syntactical unfolding which differ only for an injective substitution. To this purpose, we assume to have a normalization function norm over agents, so that if norm(P) = (/3, ~} then /5 is the representative of the class of agents differing from P only by an injective substitution (it is called normalized agent)

52 and cr : f n ( P ) --* f n ( P ) is the injective substitution such that P = Per (it is called the normalizing renaming) 4. During the construction of the unfolding, then, we still use the free names to approximate the active names, but the target of a transition is now normalized. Of course, each transition of the 7r-automaton must then store this normalizing renaming, so that the names of the target can be bounded to the corresponding names of the source. D e f i n i t l o n l 3 . The ~r-automaton corresponding to the agent P0 is the lts ~r-aut(Po) with P0 E Q as initial state and such that whenever P E Q then: 9

-

if P ~

- if P ~

T

"/'1r

?

P and ( P " , or} = norm(P') then P " 9 Q and P I ',~ P " ; e ' and ( P " , ~) = norm(P') then P " 9 Q and P *-i'Y'~-P " ;

- if P ~(-~Y)P ' , y = r a i n { A ; - f n ( P ) } and {P", a) -- norm(P') then n " 9 Q ,(y),o and P I .~. pi,; xy,o

- if P --~ P', y 9 f n ( P ) and {P", r = norrn(P') then P " 9 Q and P ! ..~P"', - if P ~ P ' , y = min{Az - f n ( P ) } and (P", it) = norm(P') then P " 9 Q ~(,),o and P I -'-~P~'. Note that the normalization function does not act on the initial state, so that its free names are exactly the free names of agent P0The sets of active names are now determined on the v-automaton essentially in the same way as in the syntactical unfolding.

I f P is a state of the 7r-automaton A, corresponding to an agent without matching, then an(P) is the smallest set such that x 9 an(P) iff

Propositionl4.

l&~rt

for some transition P I '.~P' in A we have x 9 an(l~ ) U (~(an(P')) - 5"ff(l~)) , where an(p) and "a-if(p) are defined as in Table e. We can define an efficient algorithm for finding the active names of all the states of a r - a u t o m a t o n : suppose that a name z of a state P is represented with the pair {P, z) and that G is the direct graph with all these pairs as nodes and D~O"

with an are from {P', x) to {P, a(z)) if P ~ P ' and or(x) ~ ~-ff(/~). To find the active names we can use an algorithm that identifies the nodes of G reachable from the nodes in I = { ( P , z ) I P 9 Q, PI

'..~P' and x 9 an(p)}.

From r-ant(P) and from the information on the active names of its states we can build directly irr-un3~P); we have i) to make irredundant the states of 7r-hut(P) by restricting them (thus erasing some input transitions), and ii) to replace each 4 Such a function can be obtained by defining a total ordering of the free names in an agent which depends only on the positions of the names in the syntactical tree of the agent and then by bijectively mapping these names in the initial segment of Af.

53 state of ~-aut(P) with all its versions, differing by injective substitution, that are reachable from the initial state. D e f i n i t i o n l h . Given a ~r-automaton A, the Its unw(A) corresponding to the unwinding of A is defined as follows. Its initial state is ~P0, where P0 is the initial state of A, and whenever P 9 QA and ~ ( P a ) 9 Q~,nw(A) for some injective substitution r then: ,r~o,I

- ifP I :u

then ~ ( P ' ~ ) E Q=,~(A) and ~ ( P a ) , T A~(P'~), where a = a o a ' ;

~'y,ct I

- if P [

.~ P ' , then g ( P ' ~ ) e Q~,~(A) and ~ ( P ~ ) ~ ' Y ~ ( P ' ~ ) , where ~ = r ~(y),a

I

- if P I '.b P ' , then ~ ( P ' ~ ) 9 Qunw(A) and ~ ( P a ) ~ ( ~ ) g ( P ' # ) , where z = min{Af - ~(an(P))} and ~ = {z/ya} o ~ro r if P I ~ P ' and y 9 an(P), then g ( P ' ~ ) e Q..~(a) and g(Pa) where ~ = a o a~; ~(~),a' - if P I :'~ P ' , then J~(P'~) 9 Q=,w(A) and g ( P ~ ) ~ ( ~ ) ~ ( P ' # ) , where z = min{Af - ~(an(P))} and ~ = {z/ya} o a o ~'; -

where va stays for tr(v). P r o p o s i t i o n l 6 . Given an agent P, irr-unj[P)= unw(~r-aut(P)).

Corollary 17. Given two agents P and Q, then P .~ Q iff unw(Tr-aut(P)) .~ unw( ~r-aut(Q ) ). Thus we have shown that finite irredundant unfoldings can be effectively constructed for finitary ~r-calculus agents without matching. For these agents we have an algorithm for checking bisimilarity: it first builds the irredundant unfoldings and then checks ordinary bisimilarity on these transition systems.

5

Complexity

In this section we consider the time complexity of the proposed algorithm. First we describe the time complexity of the bisimilarity test for two ~r-automata A and B as a function of the number s of their states, the number t of their transitions and the maximal number n of free names present in their states. P r o p o s i t i o n 18. Let P and Q be two finitary agents without matching and suppose that A and B are the rr-automata corresponding to them. IfIQAI, IQBI< s, 1, ~AI, I~ 'BI _< t a n d PfiQamaxIfn(P)l, ~ B Ifn(P)l _< n, the bisimilarity of P

and Q can be tested, starting from the automata, in

20(l~176176

Proof (Sketch). The proof follows from the following considerations.

steps.

54

The active names of each ~'-automaton can be computed in O(tn + (sn)2): the construction of the initial set of active names is in O(t) (we have to consider the active names deriving from each transition, and there are at most two names in each of them), the construction of the graph is O(tn) (we have to consider all the transitions and, for each transition, the names of the target state), and the search of the reachable nodes is O((sn) 2) (sn is the maximal number of pairs state-name). Each unwinding generates a Its with at most O(sn!) states and O(tn!) transitions (and can be constructed in O(n!(s + t))). - If the states and the transitions of two Its are respectively < s' and < t', the Paige-Tarjan algorithm [15] can test bisimilarity in O(t' log s' + s'). [] -

-

Now we try to determine the values s, t and n for a ~r-automaton as a function of the syntactical size k of the corresponding ~r-calculus agent: the syntactical size of an agent P is defined as the sum of the lengths of P and of all the recursive definitions used by the agent. The following proposition states that, in the general case, it is not possible for finitary agents to effectively bound the number of states of a ~r-automaton in function of the syntactical size of the corresponding agent. P r o p o s i t i o n l 9 . There is no total computable function s such that, for each finitary agent P with syntactical size k, ]Q~r-aut(P)[