+ All Categories
Home > Documents > Activity simulation in Modula-2: An exercise in language extension

Activity simulation in Modula-2: An exercise in language extension

Date post: 25-Aug-2016
Category:
Upload: eric-salzman
View: 213 times
Download: 0 times
Share this document with a friend
22
Comput. Lang. Vol. 17, No. 1, pp. 39-(o0, 1992 0096-0551/92 $3.00 + 0.00 Printed in Great Britain. All rights reserved Copyright © 1991 Pergamon Press plc ACTIVITY SIMULATION IN MODULA-2: AN EXERCISE IN LANGUAGE EXTENSION ERIC SALZMAN Department of Computer Science, University of Queensland, St Lucia, Queensland 4067. Australia (Received 10 January 1990; revision received 10 December 1990) Abstract--Discrete event simulation modelling is enhanced by the provision of adequate modelling tools to assist the programmer in defining the entities of a system, their interrelationships and how they interact over time. Several methodologies exist. We develop a high level language for the activity approach in this paper. A promising approach to developing an appropriate programming language for any application area is to adapt existing languages by restriction and extension to fit in with the problem environment. In this case, we adapt Modula-2 by severalextensions to this specificdomain. By this means, programmers already familiar with Modula-2 will be encouraged to design simulation models using features more suited to this task than by programming in the non-problem specificfeatures available in basic Modula-2. The idea of creating a hierarchy of programming languages has been proposed as the ideal language design mechanism by Bailes. The justification for this approach is the conceptual parallels between programming and language design, and the way in which programmer defined constructs are in practice not distinguished from those provided as part of the programming language. Simulation Activity modelling Translation Extensible languages INTRODUCTION The basic thrust of programmer educators is to develop an appreciation of problem specification and solution, for example using a top-down methodology refining specifications into chosen language features available in a target language environment, or by bottom-up extensions from a base language guided by the need to provide commonly required abstractions. The ideal programming language is one embracing all abstractions imaginable in the specific problem domain thereby providing the highest conceptual aids to formulate and solve some problem. Initially, a solution is encoded in this ideal language. The programmer's task is then to conceive a set of refinements invo!ving more restrictive components until at the lowest level the solution is presented solely within the features of the available target language. An as yet under-explored approach to language extension is to consider the intermediate phases as viable languages. Each language is derived by restricting and enhancing host features. Because of the close proximity of the languages, the derived language can be quickly learned by someone knowledgeable about the host language. Also, because of the nearness of the languages, translators can be quickly implemented by modifying existing translators. By this means, language extensions are possible and powerful problem specific language extensions providing necessary conceptual aids for programmers are viable. It is conceivable that by extending a common base to several application areas, a tree of languages exists: the programmer's task is to locate one that best represents his problem situation. If this language is sufficiently close to his problem domain, then the top-down methodology will ideally produce the final program with a minimum number of intermediate steps. However, where the conceptual gap is still large, it is possible that several intermediate languages providing general facilities are needed. By automating the translation, we remove a potential source of error from the programmer whose task is already difficult. Clearly the intermediate language levels must be of sufficient generality to warrant the status of a being termed a language. In extending the hierarchy from level i to level i + 1 we need: support modules written in level i; a translator which accepts a program in level i + 1 and outputs a program in level i..The modules needed to implement and support a language proposal at level i + 1 must be coded in the language of level i or lower (see [1]). In this paper, we explore extensions necessary to Modula-2 to support activity simulation modelling. For syntactic descriptions in the following, we adopt EBNF and Wirth's metasyntactic vocabulary for Modula-2. Bailes [3] justifies this approach to language design. In [1], the approach 39
Transcript

Comput. Lang. Vol. 17, No. 1, pp. 39-(o0, 1992 0096-0551/92 $3.00 + 0.00 Printed in Great Britain. All rights reserved Copyright © 1991 Pergamon Press plc

ACTIVITY SIMULATION IN MODULA-2: AN EXERCISE IN LANGUAGE EXTENSION

ERIC SALZMAN Department of Computer Science, University of Queensland, St Lucia, Queensland 4067. Australia

(Received 10 January 1990; revision received 10 December 1990)

Abstract--Discrete event simulation modelling is enhanced by the provision of adequate modelling tools to assist the programmer in defining the entities of a system, their interrelationships and how they interact over time. Several methodologies exist. We develop a high level language for the activity approach in this paper. A promising approach to developing an appropriate programming language for any application area is to adapt existing languages by restriction and extension to fit in with the problem environment. In this case, we adapt Modula-2 by several extensions to this specific domain. By this means, programmers already familiar with Modula-2 will be encouraged to design simulation models using features more suited to this task than by programming in the non-problem specific features available in basic Modula-2. The idea of creating a hierarchy of programming languages has been proposed as the ideal language design mechanism by Bailes. The justification for this approach is the conceptual parallels between programming and language design, and the way in which programmer defined constructs are in practice not distinguished from those provided as part of the programming language.

Simulation Activity modelling Translation Extensible languages

I N T R O D U C T I O N

The basic thrust of p rogrammer educators is to develop an appreciation of problem specification and solution, for example using a top-down methodology refining specifications into chosen language features available in a target language environment, or by bot tom-up extensions from a base language guided by the need to provide commonly required abstractions. The ideal programming language is one embracing all abstractions imaginable in the specific problem domain thereby providing the highest conceptual aids to formulate and solve some problem. Initially, a solution is encoded in this ideal language. The programmer ' s task is then to conceive a set of refinements invo!ving more restrictive components until at the lowest level the solution is presented solely within the features of the available target language.

An as yet under-explored approach to language extension is to consider the intermediate phases as viable languages. Each language is derived by restricting and enhancing host features. Because of the close proximity of the languages, the derived language can be quickly learned by someone knowledgeable about the host language. Also, because of the nearness of the languages, translators can be quickly implemented by modifying existing translators. By this means, language extensions are possible and powerful problem specific language extensions providing necessary conceptual aids for programmers are viable. It is conceivable that by extending a common base to several application areas, a tree of languages exists: the programmer ' s task is to locate one that best represents his problem situation. I f this language is sufficiently close to his problem domain, then the top-down methodology will ideally produce the final program with a minimum number of intermediate steps. However, where the conceptual gap is still large, it is possible that several intermediate languages providing general facilities are needed. By automating the translation, we remove a potential source of error from the programmer whose task is already difficult. Clearly the intermediate language levels must be of sufficient generality to warrant the status of a being termed a language. In extending the hierarchy from level i to level i + 1 we need: support modules written in level i; a translator which accepts a program in level i + 1 and outputs a program in level i . .The modules needed to implement and support a language proposal at level i + 1 must be coded in the language of level i or lower (see [1]).

In this paper, we explore extensions necessary to Modula-2 to support activity simulation modelling. For syntactic descriptions in the following, we adopt EBNF and Wirth 's metasyntactic vocabulary for Modula-2. Bailes [3] justifies this approach to language design. In [1], the approach

39

40 ERIC SALZMAN

is applied to functional language design, in [4] we apply the method to a data base application using a functional language host, and in [5], we exploit the strategy to provide a declarative methodology in an applicative host language.

Language requirements for activity modelling

Within the discrete event modelling arena, at least four major approaches are employed. The novice not familiar with general problem requirements will attempt to produce a specific solution to the particular modelling environment of interest. Perhaps after writing several programs and an emerging pattern develops, an event modelling approach as a general solution methodology will be tried. An event is a description of all the changes in relationships of entities within the modelled environment that take place instantaneously the event occurs. Conceptually, an event is like a procedure which is invoked at a particular instant in simulation time. A third approach is to attempt to construct the model by building descriptions of how entities interact with the system. Such descriptors are called processes. An activity involves the co-operation of resources within the system in an active (production) phase in order to produce some "thing" or achieve a goal and provides yet another approach. We consider the activities that occur in the system, and specify the conditions under which they are initiated and their operational development over time [6].

While the latter approaches lead to a cleaner encoding of the model, in looking at their implementation it becomes clear it is much simpler if the host language has a coroutine capability. This is because the process description and the activity do not execute instantaneously nor to completion when started under normal conditions within the system but instead execute piecemeal. The descriptions describe what happens until a delay is experienced at which time the activity must be put on a hold until some resource becomes available (a passive delay) or while some simulated operation takes place (an active delay). With a passive delay, the time the delay will conclude cannot generally be predicted at the point in time the delay is invoked. For active delays, the prediction of the duration is based on a random variate drawn from a distribution whose probability density function is derived from studying the system under investigation. Restricted coroutines having the structure of parameterless procedures are available within Modula-2. Perhaps the usefulness of this feature is not given adequate recognition by programmers.

The implementation strategy: creating the hierarchy All the above discrete event methodologies require facilities to generate random numbers,

maintain queues, keep system time, record statistical data, generate reports on that accumulated data, etc. In this paper we focus on those features needed to provide an activity simulation base. We extend Modula-2 in three stages. First we enhance the coroutine capability of Modula-2 to provide a more comprehensive utility by removing the restriction of no parameters. This we call CM2 for more extensive Coroutines in Modula-2. Second, we extend CM2 to provide those features common to all the simulation paradigms presented above. This extension provides facilities to maintain queues, generate random numbers, sample variables which may or may not be integrated over time, produce reports on those variables, and finally, to provide resource management capabilities. This extension we call SM2 (Simulation Modula-2). This we will then extend to a general language in which to describe activities (AM2).

These extensions require three translators: a translator to translate CM2 programs into Modula-2; a translator from SM2 input to CM2 output; and a translator from AM2 to SM2.

LEVEL 1: CM2--A GENERAL COROUTINE CAPABILITY

The language The desire here is to extend the Modula-2 language to allow parameters to coroutines. Modula-2

only permits parameterless procedures declared at the outermost level (level 0: the level of the main program) as the candidate for coroutine procedures. Suppose we wish to invoke several coroutines each of which is to control a distinct set of resources. Using standard Modula-2, the communication of the resources the coroutine is to manage can only be made via global variables. We introduce the

Activity simulation in Modula-2 41

following declaration (Coroutine Declaration) which begins with the reserved word COROUTINE:

COROUTINE ident [ FormalParameters ] MEMORY expression;

[declaration] BEGIN StatementSequence END ident;

The expression having a result of type C A R D I N A L specifies the memory requirement for the private storage associated with this coroutine's execution. Variables of ident coroutine type are declared:

VAR IdentList : ident;

The coroutine type declaration is valid only if made at level zero, i.e. not nested inside other procedures or functions. Variables of a coroutine type must also be declared at level zero, and then after the corresponding coroutine type has been declared. Also note that formal parameters include value and reference (VAR-) parameters as for procedure-declarations. (The notation adopted suggests that coroutines are a special procedure type.)

The following expression creates an instance of a coroutine: ident[(ExpList)]; where i dent is a declared coroutine type and the ExpList is the list of actual parameters having type consistent with the FormalParameters in the declaration of this coroutine type.

Thus we could assign a new coroutine instance to a suitable declared coroutine variable as:

x := ident(ExpList);

or for the parameterless case:

x := ident.

Here we follow the Modula-2 coroutine idea: the coroutine is created but its execution is delayed. When control is passed to it, execution will commence from its first statement of StatementSequence. To pass control we introduce the a new statement type, the TransferStatement: R E SU M E expression; where the expression is of some coroutine type. To reinforce that this is not a conventional call to a procedure, a new notation is used. Note that RE SUM E i dent(Expkist); will create an instance of a coroutine type which begins executing without providing an explicit reference.

Finally, to allow the main program to be regarded as a coroutine, we include the reserved word, MAI N, which allows the main program to be invoked from anywhere. It is therefore possible within the body of a coroutine (not sensible within the main program) to RESUME MAIN. Control switches to the main program and it begins executing from where it previously transferred control.

An example is presented to illustrate this language. Then we look at the translation of these constructs after looking at the support provided in Modula-2 for the above.

Example: a counter

We look at a counter consisting of an array of display positions, each position showing a digit in the range 0-9. A button on the counter is depressed and the display read increases by 1. When an individual display reaches 9, as it turns over to display 0, it engages the button of the counter on its left. We represent each display position as a coroutine in the following program. We adopt the convention of using a prefix to the definition and implementation modules which explicitly names the language.

CM2 MODULE clock;

FROM SysStreams IMPORT sysIn, sysOut; FROM TextIO IMPORT ReadCARDINAL, WriteChars, WriteCARDINAL, NewLine;

CONST TYPE

Max/Digit = 8; Position = [l..MaxDigit];

COROUTINE Clock(VAR placedigit:CARDINAL; index: Position) MEMORY 512;

BEGIN placedigit :- 0; RESUME MAIN; (* initialise and return *)

42 Emc SALZMAN

LOOP INC (placedigit) ; IF placedigit = 10 THEN

placedigit := 0; IF index < MaxDigit THEN RESUME clock[index + 1]

ELSE RESUME MAIN END

ELSE RESUME MAIN

END END

END Clock;

VAR i, advance : CARDINAL;

digit: ARRAY Position OF CARDINAL;

clock: ARRAY Position OF Clock;

BEGIN (* initialise the clock array *) FOR i:- 1 TO MaxDigit DO

clock[i] :- Clock( digit[i], i); RESUME clock [i] ;

END;

LOOP (* display meter and increment as specified *) WriteChars(sysOut,"Meter reads: ");

FOR i: = MaxDigit TO i BY -1 DO WriteCARDINAL(sysOut, digit[i])

END; NewLineisysOut); WriteChars(sysOut, "advance: "); advance:= ReadCARDINAL(sysIn); FOR i:- i TO advance DO RESUME clock[l] END;

END

END clock.

CM2 object library

In this module we provide the specifications of the abstractions COROUTINE, MAIN, RESUME, together with procedures necessary to create the COROUTINE. In particular, we provide a procedure NewCoroutine which creates the instance and returns the reference to it. All coroutines adopt the standardized form:

CoroutineProc - PROCEDURE (ADDRESS),

a general procedure requiring a single argument. For coroutines having no arguments, this is still the uniform structure we will produce and will ignore the argument. For others, the actual argument is a POINTER type, indicating a record of appropriate type holding the parameters.

DEFINITION MODULE Coroutines;

FROM SYSTEM IMPORT ADDRESS;

TYPE COROUTINE; CoroutineProc- PROCEDURE (ADDRESS); (* standard coroutine type *)

VAR MAIN: COROUTINE;

PROCEDURE NewCoroutine(p:CoroutineProc; a: ADDRESS; n: CARDINAL):COROUTINE; (* p: procedure name; a: pointer to args; n: stack space needed *)

PROCEDURE RESUME(c: COROUTINE); (* transfers from current position to resume the named coroutine *)

END Coroutines.

Activity simulation in Modula-2 43

Preprocessing CM2 into Modula-2: coroutines with value parameters only

We now look at the translation of the above CM2 constructs limiting the initial introductory discussion to value parameters only. In the translation schemes presented in this paper, the construct Italics at level i is translated into Italics at level i - 1. A coroutine declaration is:

COROUTINE ident [ FormalParameters ] MEMORY expression; [declaration] BEGIN StatementSequence END ident;

Where the FormalParameters are value parameters only, this translates into:

TYPE

identPara~tr- POINTER TO RECORD

(* each IdentList : ForraalType of the PormalParamcte~s is retained defining fields in the record *)

FormaIParameters

END;

PROCEDURE CreateidentParams (Parameters) : identParamPtr; (* The pammm=~ match i. manb=ATp¢ ~hth d~ fidds above *) (* the idmm ~ pmfix~ w~h = 'x' m mak= thmn d~dnct *) VAR imp: identParamPtr;

BEGIN NEW (trap) ; WITH trap ̂ DO

(* assign each field in the record corresponding a~tmaent *) (*eg. Pield:=xFickl; *)

END; RETURN tmp

EtCD C r e a t e i d e n t P a r a m s ;

PROCEDURE i d e n t ( Duau~rg: ADDRESS) ;'(* is of type ComutinePro¢ *) declaration; AetAtgPm. it~ttP=amPtr;

BEGIN ActArgPtr : - identParamPtr(DumArg) ; (* tYl~COetcion*) WITH ActArgPtr ^ DO State~ntSequence

(* Iranslated without modification if value parameters only *) END; DISPOSE (ActArgPtr)

END ident;

The expression ident(ExpList) where ident is a declared coroutine type translates to

NewCoroutine (ident, CreateidentParams (ExpList), ¢xpre$$ionl ) ;

expressionl being the (translation of the) memory requirement given in the ident coroutine definition. Where the coroutine type has no arguments, ident becomes NewCoroutine(ident, NIL, expression), expression being as before. In this case, the COROUTINE translates into:

PROCEDURE ident(dummy:ADDRESS) ; (* dummy is unused *) declaration BEGIN Statem~mSequence (* without change *) END ident;

The statement RESUM E x translates into RESUM E (x) where x is an expression having coroutine type. The coroutine appears as a procedure with a single argument which does not conform to the Modula-2 requirement of a parameterless procedure. However, the approach adopted is to call a standard parameterless procedure which calls this single argument procedure within its body using global variables. References to MAIN translate to the same expression.

Preprocessing CM2 into Modula-2: coroutines with reference parameters--general

The translation scheme to cover VAR-parameter types including open array types, and procedure types is covered fully in [7]. Here we introduce the translation scheme for the simpler

44 ERIC SALZMAN

cases. There are three areas of translation: the CoroutineHeading, the block associated with the coroutine definition, and the instantiation of the coroutine (i.e. the call). We first look at the CoroutineHeading. Again, we present the coroutine type declaration.

COROUTINE ident [ FormalParameters ] MEMORY expression; [declaration]

BEGINStatementSequence END ident;

We define a pointer to a record structure to contain the parameters of the coroutine-type. Thus within the TYPE section we have:

TYPE identParamsPtr - POINTER TO RECORD

(* fields created as above for value types

and as below for VAR types *)

END;

A procedure returning a pointer to such a structure holding the parameter values embraced in a coroutine activation is needed just as before. Each VAR identlist: qualident in the parameter list (excluding an open array type) is translated into a field in the argument parameter record as identmodlist: ADDRESS where each identmod is a modified identifier formed from the corre- sponding ident as identPTR, i.e. by adding the suffix PTR (or by additional change resulting in a unique identifier). The reference parameters are incorporated in the record structure with the other (value) parameters as above.

The above coroutine declaration body translates into the following:

PROCEDURE ident (paramptr: ADDRESS) ; VAR ActArgPtr : identParamsPtr;

declarations (* of usex *); [declarations (* for managing type coercions discussed below *)]

BEGIN ActArgPtr :- identParamsPtr (paramptr) ; WITH actparams ^ DO

{statements for type coercions; (* see below *)}

StatementSequence; (* see below *)

END; D:SPOSE (ActArgPtr)

END ident;

Preprocessing CM2 into Modula-2: reference parameters (primitive types, fixed arrays, records)

We look at VAR-type parameters of fixed size (e.g. id: primitive-~pe). Within the parameter passing record, we declare a field idPTR: ADDRESS. A variable id: POINTER TO type is declared in the COROUTINE. In the type-coercion section of the COROUTINE, a statement

id :" idPTR;

is included. Within the StatementSequence, each id reference is translated into id'. For example, i f id refers to a VAR INTEGER parameter, each id occurrence is replaced with id ̂ . A t the point of call where the parameter passing record is created, in the actual call to this procedure the variable ID is translated into ADR(ID).

CM2 object library implementation

An implementation of the coroutine module follows. We will need a parameterless procedure to execute all coroutines as constrained by Modula-2. In the following the procedure CoEx acts as the executor of coroutines; when CoEx is called, a global variable provides access to a record

Activity simulation in Modula-2 45

which itself indicates the (COROUTINE) procedure and points to the parameters needed for this invocation. The procdure to be invoked and a pointer to its arguments are available in a record available globally. Upon concluding, the necessary tidying up of memory must occur. The reader will best appreciate the subtleties by examining the procedures NewCoroutine and CoEx in the following implementation.

IMPLEMENTATION MODULE Coroutines;

FROM SYSTEM IMPORT ADDRESS, PROCESS, NEWPROCESS, TRANSFER;

FROM Storage IMPORT ALLOCATE, DEALLOCATE;

CONST MinSizeCoroutine = 512 ; (* sys~m pm~ minimum sL~ *) TYPE

COROUTINE = POINTER TO RECORD

Body: CoroutineProc; (* Whlchproccdure*) ArgPtr : ADDRESS ; (* i~ argum0nts bundl~d *) Proc : PROCESS ; (* the M2 PROCESS ct~ted *) WorkSpace : ADDRESS ; (* wh~ ~e work~pa~ is *) WorkSpaceSize: CARDINAL (* and how big it is *)

END;

VAR Cur : COROUT INE ; (* ~f~n~s cun~nfly ex~u~ng comu~ *)

PROCEDURE CoEx; (* a parame~r|ess proc at level 0 *)

BEGIN

WITH Cur ̂ DO

Body (ArgPtr) ; (* HERE is where it happens *)

DEALLOCATE (WorkSpace, workSpaceSize) ; DISPOSE (Cur)

END END CoEx;

(* fre~ all memory used *)

PROCEDURE RESUME(c:COROUTINE); (* swi~h~ control from Curxent W c^.Proc *) VAR LastCo: COROUTINE; BEGIN LastCo:-Cur; Cur := c; TRANSFER( LastCo^.Proc,Cur^.Proc ) END RESUME;

PROCEDURE NewCoroutine(p:CoroutineProc; a:ADDRESS; n:CARDINAL):COROUTINE;

VAR x: COROUTINE; BEGIN

IF n < MinSizeCoroutine THEN n := MinSizeCoroutine END;

NEW (x) ;

WITH x ̂ DO

Body := p;

ArgPtr := a; WorkSpaceSize := n; ALLOCATE (WorkSpace, n) ; (* get memory *) NEWPROCESS(CoEx, WorkSpace, n, Proo);

END;

RETURN x

END NewCorout ine ;

BEGIN NEW( MAIN); Cur :~ MAIN END Coroutines.

Imp~mentation examp~--preprocessmg CM2 into Modula-2

Using the translation scheme outlined, the clock example translates to the following Modula-2 program:

MODULE clock; FROM Storage IMPORT ALLOCATE, DEALLOCATE;

FROM TextIO IMPORT ReadCARDINAL, WriteChars, WriteCARDINAL, NewLine;

FROM SYSTEM IMPORT ADDRESS, ADR;

FROM SysStreams IMPORT sysln, sysOut; FROM Coroutines I~ORT COROUTINE, CoroutineProc, MAIN, RESUME, NewCoroutine;

CONST MaxDigit - 8;

TYPE Position ~ [ I.. MaxDigit];

46 ERIC SALZ~L~N

PClock - POINTER TO RECORD

placedigitPTR: ADDRESS; index: Position END;

PROCEDURE MakeClockArg( xplacedigit: ADDRESS; xindex: Position):PClock;

VAR t: PClock; BEGIN NEW(t) ;

WITH t ̂ DO placedigitPTR:-xplacedigit; index :-xindex END;

RETURN t

END MakeClockArg;

PROCEDURE Clock (param: ADDRESS) ;

VAR ClockArg: PClock; placedigit : POINTER TO CARDINAL; BEGIN ClockArg: = PCiock(param);

WITH ClockArg ̂ DO (* return after first resumption *)

placedigit := pl%cedigitPTR; placedigit ̂ :- 0; RESUME (MAIN) ;

LOOP INC ( placedigit ̂ ) ; IF placedigit ̂ - I0 THEN placedigit ̂ :- 0;

IF index < MaxDigit THEN RESUME ( clock [ index+l ] )

ELSE RESUME (MAIN)

END

ELSE RESUME (MAIN)

END END

END; DISPOSE (ClockArg)

END Clock;

VAR digit: ARRAY Position OF CARDINAL; clock: ARRAY Position OF COROUTINE;

i : CARDINAL; advance : CARDINAL;

BEGIN FOR i :- 1 TO MaxDigit DO

clock[i] :- NewCoroutine (Clock,MakeClockArg(ADR(digit[i]),i), 512);

RESUME(clock[i]);

END;

LOOP WriteChars(sysOut,"Meter reads: "); FOR i:- MmxDigit TO 1 BY -I DO

WriteCARDINAL(sysOut, digit[i])

END;

NewLine(sysOut); WriteChars(sysOut, "advance: ");

advance:- ReadCARDINAL(sysIn); FOR i:- 1 TO advance DO RESUME(clock[l]) END;

END END clock.

With the provision of these new capabilities, we restrict some features generally available. In particular, the system features NEWPROCESS and TRANSFER which the above enhance are unnecessary in CM2 and languages (in the hierarchy) based on CM2.

LEVEL 2: SM2, SIMULATION FACILITIES ON A CM2 BASE

In this extension, the object is to create a simulation dialect by extending the vocabulary of Modula-2 to include the abstract data type Queue, random number generators, procedures for sampling variates (e.g. time in system) and sampling integer variates integrated over time (e.g. number in a queue), and resource management. We define these in separate modules and subsequently for convenience wrap them up in a single module called Simulation. Many of the features here are natural extensions to Modula-2 and can be enforced in the style a Modula-2 programmer would be used to. Where a feature enhances or replaces an existing feature, a novel

Activity simulation in Modula-2 47

notation reinforces the distinction as, for example, in the coroutine level. Much of the design here is bottom-up. That is to say, it is known the facilities introduced are those shown, in the light of experience, as essential aids to model building.

In this section, we look briefly at simple definition modules for these as implementation details are well understood. Also, because these extensions do not create major translation problems we will not present the translation to CM2 in great detail.

Queues Queues are a particular modelling requirement. Entities delayed while waiting the availability

of a specific resource frequently join a queue to be reactivated when reaching the head of the queue and the resource becomes free. Here we specify the definition module for the abstract data type queue. We include those procedures generally required for FIFO operation.

DEFINITION MODULE Queues; (* ImpMmen~ a doubly linked fist of o ~ of an arbitrary type. *)

FROM SYSTEM IMPORT ADDRESS, WORD;

TYPE Queue; (* type of the queue head *) PROCEDUR~ NewQueue() : Queue; (* Initialises the head of the queue *) PROCEDURE

PROCEDURE

PROCEDURE

PROCEDURE

PROCEDURE PROCEDURE

PROCEDURE

PROCEDURE

PROCEDURE

PROCEDURE

PROCEDURE PROCEDURE

Clear(VAR H: Queue); (* will remove all objects from the queue. *)

Empty(H: Queue): BOOLEAN; (* Returns true if queue is empty. *)

Cardinal(H: Queue): CARDINAL; (* number of elements in queue. *)

First(H: Queue): ADDRESS; (* window on first element in queue. *)

Last(H: Queue): ADDRESS; (* window on last element in queue. *)

Follow(M: ADDRESS; VAR Element: ARRAY OF WORD); (* In after M *)

Precede(M: ADDRESS; VAR Element: ARRAY OF WORD); (* In before M *)

Suoc(M: ADDRESS): ADDRESS; (* window to next, NIL if none *)

Pred(M: ADDRESS): ADDRESS; (* window to previous, NIL if none *)

Out(M: ADDRESS); (* Removes M *) Into(H: Queue; VAR Element: ARRAY OF WORD); (* In at tail *) FindMember(H: Queue; VAR M: ARRAY OF WORD): ADDRESS; (* M in H *)

END Queues.

Random variates

In keeping with our above philosophy, we specify enough random variate generators to illustrate the ideas. We adopt the approach that different random number streams should if necessary be generated from independent random number streams. Random variates provide the basis for stochastic values needed in simulating random events.

DEFINITION MODULE RanVar;

(* T~s mod~e pro~des procedures m genem~ random varia~s expordNewStream, draw, randint, uniform, normal, psnorm, negexp,

geometric, Poisson, Erlang, discrete, linear, RanStream;*)

TYPE RanStream;

PROCEDURE NewStream (Seed : CARDINAL; VAR Stream : RanStream ); PROCEDURE normal (a, b : REAL; VAR Stream : RanStream) : REAL;

PROCEDURE negexp (a : REAL; VAR Stream : RanStream) : REAL;

END RanVar.

Statistics interface-time independent sampling

We include in this interface procedures necessary for sampling variates. Sampling procedures are needed to compute means, standard deviations, and histograms of random variates. A more sophisticated package could further test the samples and identify the distribution function, The problem of sampling a random variate is assisted by the features introduced here. We introduce the t y ~ RANDOMVARIATE. Declared variables of this type have to be instantiated but whenever a value is assigned, we sample the value. Declaration of a variable of this type is: variable: RAN DOMVARIATE.

48 ERxc SALZMAN

The expression CreateRANDOMVARIATE string [SAVE] returns (a pointer to) a random variable monitor which stores the string for subsequent identification of reports. The optional SAVE indicator requests that the values be saved for the purpose of producing a histogram of the values sampled, e.g.

variable := CreateRANDOMVARIATE "Wait Times" SAVE;

Whenever a value is assigned to the variable as, for example, in:

variable := expression;

the new value is noted (and saved if the SAVE option was specified). When adequate samples have been noted (usually at the end of the experiment) a report on the samples can be produced to standard output by executing a VariateReportStatement, VARIATER E PORT O N variable.

First, the module supporting this requirement is given.

DEFINITION MODULE DiscreteStats;

TYPE DSrecptr;

PROCEDURE DSNew(NameIn:ARRAY OF CH~;store:EOOLEAN): DSrecptr; (* create a new varia~ - ff s tow ~ e n S A V E o b v i a t i o n s *)

PROCEDURE DSUpdate(block:DSrecptrJ value:REAL); (* records the value *)

PROCEDURE DSResult(block:DSrecptr); (* prints report on variate *)

END DiscreteStats.

We present the translation schemes for the above. The declaration translates to: variable: DSrecptr. The assignment statement instantiating the variate translates to :

variable:= DSNew(" name of stream", TRUE); (*with SAVE*)

For the other case, the boolean argument is FALSE. The assignment of a (new) value to the variable becomes: DSUpdate(variable,expression). Finally, the VariateReportStatement becomes: DSResult (variable).

Statistics interface-time dependent sampling

For integer variates which are integrated over time, the mean, standard deviation, and the probability that the variate has specific CARDINAL values is determined. We need the simulation time and make provision for passing it as a parameter.

We introduce a new type TimeRANDOMVARIATE. A variable of this type is declared via:

variable: TimeRANDOMVARIATE;

To instantiate such a variable we have an expression as above:

variable := CreateTIMESTATISTIC "name of statistic" [SAVE];

A new statement is introduced, the SetTimeVariateStatement:

ADJUST variable BY expressionl AT expression2;

This statement modifies the variable by the INTEGER amount expression1; the time at which this change is to occur is given by (REAL) expression2.

Finally, for such variables we introduce a TimeVariateReportStatement.

TimeVARIATEREPORT ON variable;

Activity simulation in Modula-2 49

The definition of support module follows.

DEFINITION MODULE TimeStats;

TYPE IPtr; TSrecptr;

PKOCEDURE TSUpdate(block:TSrecptr;time:KEAL); (* update variable *)

PROCEDURE TSNew(variable:IPtr;time:REAL;NameIn:ARRAY OF CHAR; MinNoSamples:CARDINAL; mintime,ignoreTime:REAL; Histogram:BOOLEAN):TSrecptr;

(* create a new momwE must take min_NoSam~, ~ run for mmtimo ~ r ignoring sampMs for igno~Time, producing a hiswgram ff I-Iiswgram *)

PROCEDURE TSResult(block:TSrecptr); (* print results *)

END TimeStats.

Because the translation parallels the time independent sampling case above, we provide brief outlines only. The declaration, instantiation, SetTimeVariateStatement, and TimeVariateReport- Statement introduced above translate to:

variable : CARDINAL; (* for the declaration *) TSvariable : TSrecptr; (* of the TimeRANDOMVARIATE *)

(* instantiating a variable depends on the presence of SAVE *) TSvariable := TSNew (ADR(variable), 0.0, "name of statistic", TRUE); TSvariable :~ TSNew (ADR(variable), 0.0, "name of statistic", FALSE);

TSUpdate( TSvariable, expression2); (* the ADJUST statement *) variable :- variable + ( expressionl ); (* ( ..... ) avoids sign problem *)

TSResult( TSvariable); (* produce the report *)

Note that these packages could be enhanced in a variety of ways: to reset the sampling, to provide means, variances, histograms, number of samples, tests for normality etc., or even so that specific variates need only be sampled until the mean is measured to some prespecified half-range at some confidence limit. Such developments could be the basis for automatic stopping of sampling when all variates managed by the package have converged to the result at the accuracy requested. We desist from proposing such here as methods for provision of such facilities are well known.

Resources

Resource management can also be made extremely sophisticated (e.g. with a priority interrupt capability). Resources are the entities within the modelled environment for which processes compete. The availability status of a resource needs to be queried. Free resources can be seized for subsequent use; when no longer required they are released for use by other entities. Here we present a simple version of a resource manager in which all we do in addition to the above, is provide the ability to produce a report on the usage of the resource. To keep statistics on this, we again make provision for passing time as a parameter. We first introduce the language features. We add a new type, RESOURCE. A statement for initiating a resource (CreateResourceStatement), a statement for taking a resource (SeizeStatement) and for returning a resource (ReleaseStatement) are specified. Expressions for testing the busy/idle status of a resource are defined. Lastly, the ReportResourceStatement for producing a report on the resource's use is provided. Examples of these follow.

object: RESOURCE;

SEIZE object AT expression; (* expression is the time seized *)

RELEASE object AT expression; (* expression is time released *)

REPORT ON object; (* the report on resource usage statement *)

CL 17/I--D

50 E~c S*LZ~AN

BUSY object (* returns TRUE if resource is in use *)

IDLE object (* return TRUE if resource is free *)

object := CreateRESOURCE("the name of the object")

We n o w look at a support base.

DEFINITION MODULE Resource; (* resource are competed for- only used by one entity at a time

this p a r . ~ e defines the interface automatic stats are kept on resource c~a~d here *)

TYPE RESOURCE;

PROCEDURE CreateRESOURCE(Name: ARRAY OF CHAR): RESOURCE; (* creates a resource whose name is Name - used for reports *) PROCEDURE RESOURCEBusy(r: RESOURCE): BOOLEAN; (* return busy status *) PROCEDURE RESOURCEIdle(r: RESOURCE): BOOLEAN; (* returns not busy status *) PROCEDURE SeizeRESOURCE(r: RESOURCE; AtTime: REAL); (* use: IF RESOURCEIdle(r) THEN S ~ R F ~ O U R C E r AT expression EI~E ... END; *) PROCEDURE RoIeaseRESOURCE(r: RESOURCE; AtTime: REAL); (* release r *)

PROCEDURE ReportOnRESOURCE(r: RESOURCE); (* report to output on usage *)

END Resource.

The above translate simply to:

object : RESOURCE;

SeizeRESOURCE (object, expression) ;

ReleaseRESOURCE (object, expre$~o,} ;

ReportOnRESOURCE (oh ject ) ;

RESOURCEEusy (object)

RESOURCEIdle (object)

object :=CreateRESOURCE ("name of object") ;

The complete simulation package

We finally define the module Simulation which provides all the definitions in one module

CM2 DEFINITION MODULE Simulation;

FROM SYSTEM IMPORT ADDRESS, WORD; (.

Within this definition module, all the definitions in the modules Queues, RauVar, DiscreteStats, Time, Stats, Resources are repeated. Within the implementation module they sse implemeucA in tem~ of calls upon the originals, eg. Queue = Qaeue~. Queue

,) END Simulation.

To incorporate the above in the environment, the programmer writes the program thus:

SM2 MODULE ProgName;

program text with uses the

identifiers, expressions, statements as specified above

and any valid CM2 statement.

END ProgName.

Activity simulation in Modula-2 51

The above translates quite simply into the following CM2 program:

CM2 MODULE ProgName;

IMPORT Simulation;

*Statements defined at this level are translated as * indicated above, possibly with interface identifiers

* to constants, types, procedures, functions

*prefixed with 'Simulation.'

*Permitted CM2 statements are translated unaltered.

*Any modules using the Simulation features need to have an * IMPORT Simulation;

* statement in their header, and a chain of such declarations to

* bring the features into scope.

* Hence the desire to incorporate them within one module. ) ,)

END ProgName.

The issue of importing the simulation module internally across module boundaries to the module in which it is used complicates an otherwise trivial translation! The output from translating the above must be input to the CM2 to Modula-2 translator.

AN A C T I V I T Y L A N G U A G E

Within the language proposed, we introduce activity definitions and statements for managing activities. As well, we introduce improved statements for managing resources and sampling variates which previously needed a time specified. Within the simulation environment, the activity essentially captures the notion that resources within the environment co-operate in some active phase or succession of active phases. The following language constructs are proposed. We add to declaration, an ActivityDeclaration which has two forms distinguished by the presence of WHEN or I_OOPWH £N.

ACTIVITY ident [{ FormalParameters )] MEMORY expression;

[LOOP]WHEN expression

[VAR

[VariableDeclaration} [INITIALLY StatementSequencel ]]

BEGIN StatementSequence2

END ident;

The semantics of these follow. In each case, once an activity has been created, the when expression is a condition specifying when the activity may commence. The condition is expressible in terms of global variables only and should not involve simulation time. Reasons for this restriction will become apparent when scheduling techniques are presented. The BEGIN.. .END brackets a StatementSequence2 in which the VariableDeclarations are the local variables and statements are translatable directly into SM2, the level below AM2 in the hierarchy. Local variables may be initialized within the INITIALLY-clause. StatementSequencel is provided to initialize the local variables and will in most cases be a sequence of assignment statements. We call the StatementSequence2 the Modus Operandi of the activity.

The operational difference in the two constructs is that the WH £N. . . £N D construct is executed once and the activity no longer interacts with the system. In the LOOPWH £N. . .£N D construct, when the activity has completed its Modus Operandi, it is automatically replaced in the system such that when the condition given in expression again becomes TRUE, it will re-execute. If it is T R U E immediately, then the activity restarts at once. There is no re-execution of StatementSequence I, the initial state of local variables being the final state of the previous iteration. Note also that no activity managing statement (see below) can occur in StatementSequencel.

52 ERIC SALZMAN

Additional statements for managing activities are required to initiate an activity instance, to conclude a looping activity, and to cause an active delay. Firstly, to initiate an activity, we have an ,4ctivationStatement.

ACTIVATE QualIdent [ActualParameters] [PRIOKITY SimpleExpression]

The ConcludeStatement: CONCLUDE; is valid within a LOOPWHEN type activity in StatementSequence2 and forces the activity to stop looping immediately. The statement normally appears as the ultimate statement in the major loop of the Modus Operandi. The HoldStatement: HOLD expression; forces an active delay of the activity by the amount of simulation time given by the (real and positive) amount expression. Negative amounts are treated as no delay. Passive delays are not specifically requested within the Modus Operandi but are implied by the condition at the start of each activity specification. The expression TIM E returns the simulation time. The StartSimulationStatement and StopSimulationStatement statements are STARTS I M U I_ATI O N and STOPSI M UI_ATION. The former appears in the main program after the initialization to start the simulation proper. Thus the statement should be executed only after all initial activities have been created. The StopSimulationStatement appears in any activity which is capable of detecting that the conditions of the experiment have been fulfilled. It causes an immediate termination of that activity and the scheduler controlling the simulation. The main program is resumed at the statement after STARTSIMULATION where it has been in limbo for the duration of the run.

(Aside. We advise that the structure of the activity take the following form:

get all resources needed; (* tested in WHEN ... *) HOLD ... ;

release a resource;

HOLD ... ;

release a resource;

HOLD ... ;

release a resource;

• . o ;

This approach avoids deadlock problems wherein several activities start each under the impression that all its required resources are available and not reserved for use by other activities. Taking all resources initially before any time delay occurs within the body of the activity avoids a deadlock situation occurring. All (global) resources needed for the activity should be tested within (expression) in the [LOOP]WHEN statement. Thus the general form that the conditional expression should take is:

[LOOP]WHEN ResourceFree (A) AND (ResourceFree (B) OR ResourceFree (C)) . . .

End Aside)

Finally, we simplify the statements for taking and releasing a resource, and for adjusting a time dependent statistical variable. We assume the time field is the simulation time the statement is invoked.

The SeizeResourceStatement is

SEIZE object;

where object is of type RESOURCE. The Re~aseResourceStatement is:

RELEASE object;

The SetTime VariateStatement is:

ADJUST variable BY expression;

With the enhanced activity handling statements introduced here, we suggest that restricted use be made of low level coroutine managing statements introduced into an earlier level. The

Activity simulation in Modula-2 53

SeizeResourceStatement, ReleaseResourceStatement, and SetTimeVariateStatement are valid in the redefined formats only.

A simple activity model

As an example, suppose a garage employs an attendant for serving fuel, and a mechanic repairs cars booked for service. After a car is filled, if it is towing a boat then that is filled. The driver than pays the attendant who registers the sale. After a repair, the mechanic records the payment using the same register. We wish to examine the time a car being fuelled spends in the system, analyse the numbers of cars in the system awaiting or being repaired, and investigate the attendant's work pattern.

We present an outline of the garage model in sufficient detail to demonstrate the language features.

Activity MODULE garage;

FROM TextIO IMPORT ...; FROM SysStreams IMPORT ... ; FROM Storage IMPORT .... ;

TYPE Car=POINTER TO RECORD HasBoat: BOOLEAN; InAt: REAL END;

VAR Attendant, Mechanic, Register: RESOURCE; NumFuelThru: CARDINAL;

FuelQueue, MechRepairQueue: Queue;

TimeInSystem: RANDOMVARIATE; N~erRepairs: TimeRANDOMVARIATE;

ACTIVITY Fill MEMORY 512; (* with stream for random fill time ignored *) LOOPWHEN (NOT Empty(FuelQueue)) AND IDLE Attendant

VAR ThisCar: Car;

BEGIN SEIZE Attendant; ThisCar := First( FuelQueue); Out(ThisCar); HOLD ...

IF ThisCar ̂ . HasBoat THEN HOLD ... END;

ACTIVATE RegisterFuelSale(ThisCar) PRIORITY 5;

END Fill;

ACTIVITY RegisterFuelSale( C: Car) MEMORY 512; (* random time ignored *) WHEN IDLE Register

BEGIN SEIZE Register; HOLD .... ; RELEASE Register; RELEASE Attendant; TimeInSystem := TIME - C ̂ . InAt; DISPOSE(C); (* return to world *) INC(NumFuelThru); IF NumFuelThru=2000 THEN STOPSIMULATION END;

END RegisterFuelSale;

ACTIVITY MechanicRegister MEMORY 512; .......

ACTIVITY FuelArrivals MEMORY 512;

LOOPWHEN TRUE

VAR CarVar: Car;

CarArrivalStream, Boat: RanStream; ArrivalStreamSeed, BoatStreamSeed: CARDINAL; RecipMeanTimeBetweenArrivals, ProbBoat: REAL;

INITIALLY

RecipMeanTimeBetweenArrivals := 1.0 / ReadREAL(sysInl;

ArrivalStreamSeed :- ReadCARDINAL(sysIn); NewStream(ArrivalStreamSeed, CarArrivalStream); ProbBoat:= ReadREAL(sysIn); BoatStreamSeed :- ReadCARDINAL(sysIn); NewStream(BoatStreamSeed, Boat);

BEGIN (* s~y m ~liS cycle *) HOLD negexp(RecipMeanTimeBetweenArrivals, CarArrivalStream); NEW(CarVar); CarVar ̂ . InAt :- TIME; CarVar ̂ . HasBoat := draw( ProbBoat, BoatStreamSeed); Into( FuelQueue, CarVar);

END FuelArrivals;

ACTIVITY RepairArrivals MEMORY 512 ; (" ~ ~r ~el ar~v~s *) ...

BEGIN { maL~ p~gnun ]

Attendant : = CreateRESOURCE ("Attendant") ;

54 EPac SALZMAN

Mechanic :~ CreateRESOURCE(...);

Register :~ CreateRESOURCE(...); NumberRepairs := CreateTIMESTATISTIC("Cars for repair") SAVE; FuelQueue := NewQueue(); NumFuelThru := 0; MechRepairQueue :~ NewQueue()~

ACTIVATE FuelArrivals PRIORITY 20; ACTIVATE RepairArrivals ...;

ACTIVATE Fill PRIORITY i0; ACTIVATE Repair ...;

STARTSIMULATION;

REPORT ON Attendant;

VARIATEREPORT ON TimeInSystem; TimeVARIATEREPORT ON NumberRepairs;

END garage.

Scheduling issues

We digress before examining the implementation module to consider a scheduler capable of supporting our modelling philosophy. The approach adopted is that the highest priority activity capable of being run next is the one we require to be resumed.

The scheduler uses two lists. One list will maintain those activities in the [LOOP]WHEN Expression phase; i.e. they are passive waiting for resources. These activities will be maintained in decreasing priority order with the time the delay was instigated being a secondary key in ordering activities with the same priority. The other list is the set of activities which have started, collected the resources needed, and are somewhere in the body of the modus operandi in a HOLD or currently working (i.e. they are active). Such activities will be maintained in time to resume order with decreasing priority as the secondary key. The scheduler operates as follows (in loose Modula-2): (Active = active queue of activities: Passive = passive queue of activities).

REPEAT IF Passive queue is NOT Empty THEN (* set HighestPr to priority of Active activity runnable now *) IF (Active is NOT Empty) AND (its First can go now) THEN

HighestPr :- priority of First in active (* highest *)

ELSE HighestPr := MININT

END; Try := First in Passive Queue~ Started:- FALSE; WHILE Try's.priority is greater than HighestPr:DO

Resume Try; IF Try can start THEN (* activity must corm~unicate this *)

take Try Out of Passive; Try's^.Time :- currenttime; put Try at front of Active;

EXIT the WHILE LOOP

END; IF Empty(Passive) OR no more in Passive THEN

EXIT ELSE

Try := Try's successor in Passive Queue

END; END; (* WHILE")

END; (* IF Passive queue is NOT Empty *);

IF Active is Empty THEN ERROR (* no process to activate now *)

ELSE (* first in Active can be resumed *) NextAct := the first activity in Active;

take NextAct out of Active; currenttime := NextAct's Time; Resume NextAct; (* may conclude- stop all *)

IF NextAct has terminated THEN

DISPOSE(NextAct) END

END (* IF Empty(Active) *) UNTIL sUop simulation; (* some activity has stopped simulation *)

RESUME MAIN (* finish up *)

Activity simulation in Modula-2 55

The pragmatics are that the body of code implementing this scheduler will be a separate coroutine so that activities can resume this scheduler readily from the point in the scheduler where the activity was invoked. Finally, when all is done, the main program is resumed.

AM2's object library

The support module written in SM2 is now presented. Firstly its definition which is largely determined by the translation scheme we propose for activities.

Simulation DEFINITION MODULE Activity;

FROM SYSTEM IMPORT ADDRESS;

TYPE ActivityProc- CoroutineProc;

PROCEDURE Time() : REAL; (* ReV.u'ns the system simulation time. *)

PROCEDURE Activate(Act:COROSr17NE; Priority: CARDINAL);

PROCEDURE Hold(Delay: REAL); (* Suspend ~e current acfivi~ for ~e specked delay.*)

PROCEDURE StartSimulation; (* Start ~e sim~afion; call this after m i ~ l i ~ o n completz *)

PROCEDURE StopSimulation; (* Call this m stop ~e simu~fion ~te~ you have fruited. *)

PROCEDURE StartModusOperandi; (* call genenu~ when an ~f ivi~ can kick away m when-con~tion TRUE* )

PROCEDURE ReturnToScheduler; (* inserted m code w mtum w ~hedd= ff when-condition still FALSE *)

PROCEDURE ReturnToPassive; (* ~tttrns active ~fivity m p~mv¢ queue *)

PROCEDURE ActivityConcluded; (* called ~ ~fivity finishs; allows memory mwmgement *)

END Activity.

Translation scheme

We now define the translation scheme for AM2 into SM2. Code outlines will be presented.

AM2 MODULE ident; stuff

END ident.

translates into

SM2 MODULE ident; FROM Activity IMPORT ..... ;

END ident.

The activity module:

ACTIVITY Ident [(params)] MEMORY expression; WHEN expression

[VAR {VarDeclaration} [INITIALLY {AssignmentStatement} ] ]

BEGIN StatementSequence

END Ident;

56 ERIC SALZMAN

translates into:

TYPE COROUTINE Ident [ (params) ] MEMORY expression;

[ VAR { VarDecl~ion } ] BEGIN

{AIsigluTlentSlateraent} (* initialize local variables before start *) WHILE NOT ( ~pression ) DO (* stay in this loop until expression *)

KeturnToSoheduler (* return without indicating can start *) END; StartModusOperandi; (* a return indicating this can start *) StatementSequence; (* do the modus operandi *) ActivityConcluded (* set indicator to deallocate memory *)

END Ident;

Similarly,

ACTIVITY Ident [(params)] MEMORY expression; LOOPWHEN expression

[VAR {VarDeclaration} [INITIALLY {Assign~,entStatement} ] ]

BEGIN StatementSequence

END Ident;

translates into:

TYPE COROUTINE Ident [ (params) ] MEMORY expression;

[ VAR {VarDeclaration } ] BEGIN

{AssignraentStatement } (* initi~li,¢ locals*) LOOP

WHILE NOT ( expression ) DO (*loop und| expr~sion *) ReturnToScheduler (* res~e sch~du]~ *)

END; StartModusOperandi; (* tell sched, d~ have sL~d*) StatementSequence; C do modus operandi *) ReturnToPassivate (* in passive; call scheduler*)

END (* LOOP *); ActivityConcluded (* flag to deaUoca~ memory *)

(* resume scheduler *) END Ident;

The remaining translation schemes are straight forward.

ACTIVATE Ident [ ({ExpList }) ] PRIORITY expression;

becomes

Activate ( Ident [ ( {Ex~/st})], expression);

The ConcludeStatement, CO NCLU DE, can only occur within the context of a LOOPWHEN- type activity body. In simple cases CO N C LU D E translates to EXIT. However, where CO N C LU D E itself occurs in a nested set of looping statements we need to be able to terminate all loops and the coroutine as well. The translation scheme involves declaring a boolean XYZConcludeActivit7: BOOLEAN; which is initialised to FALSE; then the ConcludeStatement becomes

XYZConcludeActivity:-TRUE; EXIT;

After each looping statement (WhileStatement, RepeatStatement, ForStatement, and LoopState- ment), we put the statement

IF XYZConcludeActivity THEN EXIT END;

Activity simulation in M o d u l a - 2 57

This takes control to the point after the L O O P . . . E N D statement generated from the user's L O O P W H E N . . . E N D at which point the above is not inserted.

TIME translates into TIME(). HOLD expression translates into Hold (expression).

The statements for seizing, releasing of resources and SetTimeVariateStatement are readily translated. They become:

SEIZE object AT Time(); RELEASE object AT Time (); ADJUST variable BY expression AT Time();

Points to note

When an activity is in the Passive queue and is able to start and escape from its initial W H I L E loop, it returns to the scheduler via the path StartModusOperandi, otherwise it returns via 8eturnToSchoduler. The former sets a flag to indicate that the most recently tried activity has started. When some activity in the Passive queue can start, no further passive activities are investigated; the activity is immediately put at the head of those activities in the Active queue waiting on some time delay such that it will be resumed immediately without advancing time. When a looping activity has exhausted the statement list forming its modus operandi, it is returned to the passive set via ReturnToPassive. In this situation, the returned activity is the one currently executing. ActivityConcluded is a return indicating the currently executing activity has concluded and the memory allocated can be reclaimed.

The other interface procedures have an obvious behaviour. HOLD is executed by the currently executing activity. This activity will be repositioned in the queue so that it can be resumed when the correct simulation time is reached. STARTSIMULATION merely kicks the scheduler coroutine into life. STOPSIMULATION sets a flag so that when the scheduler is selecting the next activity to run, it only does so if this flag is unset. If the flag is set, it resumes the main program (at the statement after STARTSIMULATION).

A M2--object library implementation

The implementation module in SM2 which supports AM2 is presented below.

SM2 IMPLEMENTATION MODULE Activity;

FROM SYSTEM IMPORT PROCESS, NEWPROCESS, TRANSFER, ADDRESS, MAXINT, MININT;

FROM Storage IMPORT ALLOCATE, DEALLOCATE;

TYPE Activity=POINTER TO RECORD Time: REAL; (* event time *)

Priority: INTEGER; MO: COROUTINE; (* Modus Operandi from NewActivity *) END;

VAR currenttime: REAL; (* Current system time *) MainAct, (* main program viewed as an activity *)

CurAct: Activity; (* CURrent ACTivity *) Concluded, (* Have we finished the simulation *) Started, (* Did a passive activity get started *)

DeallocateActivit y: BOOLEAN; Scheduler: COROUTINE; (* Should the scheduler deallocate CurAct? *) Passive, (* Queue of activities waiting on resources *)

Active: Queue; (* Sequencing queue for events *)

PROCEDURE ResumeAct(Act: Activity); BEGIN CurAct := Act; RESUME Act^.MO

END ResumeAct;

COROUTINE SchedulerBody MEMORY 2048 ; (* implements the scheduling algorithm discussed previously *)

CL 17 I-D*

58 emc SALZMAN

VAR

Change, NotSearchAll: BOOLEAN;

Win: POINTER TO Activity;

NextAct : Activity; LowestPr : INTEGER;

BEGIN

REPEAT

Change :m FALSE;

IF NOT Empty(Passive) THEN

IF NOT Empty(Active) THEN Win := First (Active) ;

WITH Win ̂ ^ DO NotSearchAll :- (Time - currenttime); IF NotSearchAll THEN LowestPr := Priority

ELSE LowestPr :-MININT END

END (* WITH *)

ELSE NotSearchAll :- FALSE; LowestPr :- MININT

END (* IF *);

Win :- First (Passive) ;

Started:- FALSE; LOOP (* Check Passive queue for an Activity ready to run *)

WITH Win ̂ ^ DO IF Priority <- LowestPr THEN EXIT

ELSE ResumeAct (Win ̂)

END;

IF Started THEN

Out (Passive, NextAct) ; Change :- TRUE;

NextAct^.Time :- currenttime;

Rank(Active, NextAct); 4" order by priority *)

Started :- FALSE;

EXIT END

END; Win :- Succ (Passive) ;

IF Empty(Passive) OR (Win = NIL) THEN EXIT END

END

END;

IF NOT Empty(Active) THEN (* processes to activate now? *)

Change := TRUE;

Win := First (Active) ;

WITH Win ̂ ^ DO

currenttime := Time;

Out (Active, NextAct) ; ResumeAct (NextAct); (* may return via StopSimulation *) IF DeallocateActivity THEN (* Current has terminated *)

DISPOSE (CurAct) ;

CurAct :- NIL; DeallocateActivity := FALSE

END

END 4" WITH *)

END 4" IF NOT Empty(Active) *)

UNTIL Concluded OR NOT Change;

IF NOT Change THEN

HALT (* the simulation has terminated abnormally *) END;

RESUME MainAct^.MO (* finish up *) END SchedulerBody;

PROCEDURE Time(): REAL;

BEGIN RETURN currenttime END Time;

PROCEDURE Activate(Acty:COROUTINE; Priority: CAKDINAL);

(* Create the new activity with the given parameters: MsOn: Statement part of activity

Priority: Priority of this activity.

Args: Arguments for this activity. *)

Activity simulation in Modula-2 59

VAR Actty: Activity; BEGIN NEW(Actty); Act^.MO :- Acty; Act^.Priority :- Priority;

Rank(Passive,Actty); END NewActivity;

PROCEDURE Rank(Q: Queue; Act: Activity); (*

Insert the activity into the given queue in the appropriate place according to its priority and event time.

*)

VAR Win: POINTER TO Activity;

BEGIN ...... END Rank;

PROCEDURE Hold(Delay: REAL); (* Suspend the current activity for the specified delay. BEGIN

WITH CurAct ̂ DO Time :- currenttime + Delay END; Rank(Active, CurAct); RESUME Scheduler

END Hold;

*)

PROCEDURE StartSimulation; (* Start the simulation; call after finished initialisation. BEGIN RESUME Scheduler END StartSimulation;

*)

PROCEDURE StopSimulation; (* Call this to stop the simulation after you have finished. *) BEGIN Concluded :- TRUE; RESUME Scheduler END StopSimulation;

PROCEDURE StartModusOperandi; (* called when a si~,ulation activity starts as condition is now TRUE *) BEGIN Started := TRUE; KESUME Scheduler END StartModusOperandi;

PROCEDURE ReturnToScheduler;

BEGIN RESUME Scheduler END ReturnToScheduler;

PROCEDURE ReturnToPassive; BEGIN Rank(Passive, CurAct); RESUME Scheduler END ReturnToPassive;

PROCEDURE ActivityConcluded;

BEGIN Deallocated := TRUE; RESUME Scheduler END ActivityConcluded;

BEGIN Active := NewQueue(); Passive := NewQueue(); currenttime := 0.0; DeallocateActivity := FALSE; Concluded := FALSE;

Scheduler := SchedulerBody; NEW(MainAct); CurAct := MainAct;

WITH MainAct ^ DO Time := 0.0; Priority := MAXINT; MO :s MAIN END END Activity.

CONCLUSIONS

Our objectives have been two-fold: to produce a language by hierarchical extension, and to design a language useful in a specific application area. The measure of the success of a design can only be gauged by its acceptance by programmers employed in solving problems in this domain. Without polished translators to assist in this task, the reasonableness of the language proposal cannot be ascertained.

However, we have demonstrated that enhancing a host language with adequate features intrinsic to some problem domain is a viable technique for making new methodologies rapidly available in familiar environments. This idea of adaptation by extension and restriction reduces the need for significant programmer retraining and makes the transition as gentle as possible. The approach is

60 ERIC SALZMAN

not new as we have seen Structured Fortran [8-10], the C language ex tended with classes [11], Pascal Plus for da t a base work [12], extensions to M o d u l a - 2 to suppor t classes [13], and logic programming [14].

Clear ly, a p r o g r a m m e r a l r eady fami l ia r with M o d u l a - 2 will ad jus t quickly to new p rob l e m specific languages largely based in the M o d u l a - 2 host. The language i tself should be readi ly learned; the m a j o r advan t age being the increased p roduc t iv i ty in work ing with a l anguage which readi ly p roduces a p rob l em so lu t ion because o f the presence o f sui table concepts in the language.

Curren t ly , we have pe r fo rmed the above t rans la t ions by hand to test the viabil i ty. W e are look ing at me thods for specifying and ca r ry ing out these a d a p t a t i o n s efficiently and quickly. A n effort a t mod i fy ing a mul t i -pass compi le r which pe r fo rmed type analysis on a late pass presented a w k w a r d p rob l ems which wou ld be a l levia ted in a single pass compi le r o r in compi le rs specifically deve loped to a l low extensions.

R E F E R E N C E S

1. Bailes, P. A. and Salzman, E. J. A prototype development of a functional language hierarchy. Proceedings of the 2~d Australian Computer Engineering Conference 1986, pp. 99-108; 1986.

2. Wirth, N. Programming in Modula-2, 3rd corrected edition. New York: Springer; 1985. 3. Bailes, P. A. The programmer as language designer (towards a unified theory of programming and language design).

Proceedings of the 1st Australian Software Engineering Conference, pp. 14-18; 1986. 4. Bailes, P. A. and Salzman, E. J. Software development by functional language protyping. Technical Report 76,

Department of Computer Science, University of Queensland; 1987. (Also to appear in Computer J.) 5. Bailes, P. A. and Salzman, E. J. DM2--a declarative dialect of Modula-2 for rapid prototyping. Technical Report 91,

Department of Computer Science, University of Queensland; 1988. 6. Banks, J. and Carson II, J. S. Discrete-Event System Simulation. Englewood Cliffs, N.J.: Prentice-Hall; 1984. 7. Salzman, E. J. Activity simulation in Modula-2--an exercise in language extension. Technical Report 95, Department

of Computer Science, University of Queensland; 1988. 8. Anderson, P. G. Structured Programming Style Manual for FORTRAN Programming. Newark: New Jersey Institute

of Technology; 1976. 9. Gales, L. E. Structured FORTRAN with no preprocessor. ACM SIGPLAN Notices 10, No. 10: 17-24; 1975.

10. Kernigan, B. W. RATFOR--a preprocessor for a Rational Fortran. Softw. Pract. Exper. 5" 395--406; 1975. 11. Stroustrup, B. The C + + Programming Language. Reading: Addison-Wesley; 1986. 12. Hughes, J. G. and Connolly, M. A portable implementation of a Modula multiprocessing database programming

language. Softw. Pract. Exper. 16: 925; 1986. 13. Rovner, P. Extending Modula-2 to build large, integrated systems. IEEE Softw. 3, No. 6: 46-57; 1986. 14. Muller, C. Modula-Prolog: A software development tool. IEEE Softw. 3, No. 6: 39-45; 1986.

About the Author--Eric John Salzman received the B.Sc. from the University of Queensland in 1962, where he also completed the Diploma of Computer Science in 1971. In 1978 he received the M.Sc. from the University of Newcastle-upon-Tyne. Initially a teacher, Mr Salzman lectured mathematics at the Queensland Institute of Technology before taking his current position at the University of Queensland. He has maintained a continuing interest in education being involved in curricula design for high school mathematics and computing studies. With several colleagues, he has proposed a 4-year university computing engineering degree. His research interests include parsing, language design, simulation methodology, and functional programming as a specification tool.


Recommended