53

Perlis a Definition of Formula Algol Mar66

  • Upload
    elfranz

  • View
    217

  • Download
    0

Embed Size (px)

Citation preview

Page 1: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 1/53

Page 2: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 2/53

A DEFINITION OF FORMULA ALGOLt

Alan J. Perl is

Renato I tu r r iagat t

Thomas A. Standishtt t

. t The research reported here was supported by the Advanced Research

Projects Agency of the Department of Defense under Contract SD-146to the Carnegie Ins t i tu te of Technology.

t t Par t ia l ly supported by the National University of Mexico and the

Inst i tuto Naciona1 de 1a Investigacion Cientif ica .

t t tNationa1 Science Foundation graduate fellow.

This paper was presented a t the

Symposium on Symbolic and Algebraic Manipulation

of the

Association for Computing Machinery, Washington, D.C.

March 29-31, 1966.

Page 3: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 3/53

ACKNOWLEDGEMENT:

We . ' ~ : t : e grateful to Professor Robert' W. Floyd and L. Stephen Coles

for numerous helpful suggestions regarding the preparation of the

manuBcript.

Page 4: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 4/53

ABSTRACT

Formula Algol is an extension to ALGOL 60 incorporating formula

manipulation and l i s t processing. This paper defines a current

version of th e Formula Algol language which' is implemented on the

CDC G-20 •

Page 5: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 5/53

1. Contents and General Description

1.1 Contents

1. Contents and General Description

2. The and s ~ b o l Declaratioris

3. Formula Expressions and Symbolic Expressions

3.1 'Formula Expressions

3.1.1 Syntax

3.1.·2 Examples

3.1.3 Semantics of A r i ~ h m e t i c , Boolean,

Conditional, Procedure, Array,

and Assignment Formulae

3.1.4 Evalua'tion Rules and Evaluated

Formulae

3.1.4.1 Syntax

3.1.4.2 Examples

3.1.4.3 Semantics

3.2 Symbolic Expressi9ns

3.2.1 Syntax

3.2.2 Examples

3.2.3 Semantics

3.2.4 Lists

3.2.4.1 Syntax

3.2.4.2 Examples

3.2.4.3 Semantics

3.2.5 Description Lists

3.2.5 .1 ,Syntax

3.2.5.2 Examples

3.2.5.3 Semantics

3.2.6 ,Selection Expressions

3.2.6. 1 Syntax,

3.2.6 .2 , Examples

3.2.6.3 Semantics

Page 6: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 6/53

4. Predicates for Formulae and List Structures

. 5.

4.1 Formula Patterns

4.1.1 Syntax

4.1.2 Semantics

4.1.3 Examples

4.2 . List Patterns

4.' 2.1 Syntax

'4.2.2 Semantics

4.2.3 Examples

4.2.4 Equality Tests

4.2.5 Testing for types

4.2.6 Testing for Membership in a Class

4.2.6.1 Syntax

4.2.6.2 Semantics and Examples

Other Kinds of Statements and Expressions

5.1 Push Down and Pop Up Statements

5.1.1 Syntax

5.1.2 Examples

5.1.3 Semantics

5.2 Additional Types of For Statements

5.3

5.4

5.2.1 Syntax

5.2.2 .Examp1es

5.2.3 Semantics

Editing Statements andEditing Statements

5.3.1 Syntax

5.3.2 Semantics

5.3.3 'Examples

5.3.4 Description List

Transformed Formulae

5.4.1 Syntax

5.4.2 Examples

5.4.3 Semantics

Description List

Editing Statements

Page 7: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 7/53

6. Special Functions

7. History and Implementation

Page 8: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 8/53

1.2 GENERAL DESCRIPTION

Formula Algol i s an extension of ALGOL 60 [1] incorporating formula

manipulation and l i s t processing. The extension is accomplished by add

in g two new types of data structures: formulae and l i s t st ructures , and

by adding an appropriate se t of processes to manipulate them. The control

,structure of ALGOL 60 is inherited without change. The resulting language

i s suitable for expressing a class of formula and l i s t structure manipula

t ions. Algorithms may be written to construct at run-time algebraic

formulae, Boolean formulae, and l i s t st ructures . Operations are available

which a l te r or combine formulae and l i s t st ructures , and which access

arbitrary subexpressions. Formulae may be evaluated, substi tuting numerical

or logical values for occurrences of variables contained within. They may

be subjected to substitutiori processes causing the replacement of occurrences

of variables by designated formulae. They may be subjected to processes of

algebraic or logical transformation defined by sets of algebraic or logical

rules in a fopn akin to Markov algorithms. Predicates are available to deter

mine precisely th e structure and composition of any formula constructible,

and mechanisms are provided to extract subexpressions of a formula provided

i t s structure is known. Likewise, predicates exist to determine the

structure and composition of any l i s t structure constructible ' , and mechanisms

are provided to extract sub1ists and subexpressions. Numerical, logical ,

and formula values may be stored as elements in l i s t structures and re t r ieval

mechanisms exist to select them for use as constituents in other processes.

Description l i s t s composed of attr ibutes and associated value l i s t s may be

attached to l i s t structures and, in part icular , to symbol variables, and ,pro

cesses exist: for ret r ieving value l i s t s and for creating, altering, and

deleting at t r ibute-value l i s t pairs . Push down stacks of arbitrary depth, are

Page 9: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 9/53

- 2 -

available for the storage of l i s t structures and, in part icular , single

symbols, and generators are provided in the form of neW types of for

statements which ~ s ' s i g n to;controlled variables the elements of a single

l i s t struc,ture" or alternatively, of several l i s t structures in parallel ,

, for use in an arbitrary process. Several special functions in the form

of standard procedures are available for the purposes of creation of names

a t run-time, testing th e current size of the available space l i s t , taking

a derivative of a formula with respect to given formula variable, erasing

l i s t structures, ' and so on. Finally, both arrays and procedures may be

defined to have formulae or l i s t structures as values.,

2. The ~ a n d s ~ b o l ,Declarations

In ALGOL 60 vat'iablesmay be declared for each possible type of data,

e.g. real , integer, Boole,an. In Formula Algol, two new data types form and

symbol corresponding to formulae and l i s t structures respectively may be

used to declafe identif iers , arrays, or procedures. That, is , l i s t s of

identif iers may be declared permitting assignment of formulae or l i s t struc-

tures to each as values, arrays may be declared having formulae or l i s t

structures as elements,or procedures may be declared whose values are data

structures of either of these two types.

When the form and symbol declarators are used in th e declaration of

simple variables, not only is storage reserved for each variable but a side

effect occqrs in which the value of each variable is ini t ial ized to the name

of th e variable. Thus, in the declarations form F,G and symbol S,T, the

atomic formula names F,G and th e atomic symbol names S,T are created and

assigned as the values of F,G,S, andT respectively.

An additional property of an identif ier X, declared either of type form- , -

Page 10: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 10/53

- 3 -

,

or of type symbol, is that X may have a description l i s t associated with

i t into Which attr ibutes and values may be entered and retrieved. Further

more, i f X is of type symbol, X names a push down stack intownich may be

storedl i s t

structures and their degenerate cases, symbols, and data terms.

3. Formula Expressions and Symbolic Expressions

3 .1 Formula Expressions

.3.1.1 Syntax

<formula expression> ::= < a ~ i t h m e t i c expression> I

<Boolean expression> I <an arithmetic expression

(Boolean expression) in which some of the primaries

(Boolean primaries) have been replaced by formula

primaries or in which some operators have been pre-

fixed with a dot>t I <assignment formula>

<formula expression> <the mark "I"> <identifier>

<the mark "'I"> <formula expression>

<formula primary> ::= <array formula> I <procedure formula> I

<transformed formula> I <evaluated formula> I . <identifier>

<conditional formula>

<array f o ~ u l a > ::= <array identifier> • [<subscript l ist>]

<procedure formula> : := <procedure identifier> '.

<actual parameter part>

<,transformed formula> : := <identifier> t <schema variable>

<conditional formula> ::= .i f

<formula expression>

<formula expression> else <formula 'expression>

t This is a short description pf what could be a formal syntactic statement.

Page 11: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 11/53

.. 4 ...

<assignment formula> ::::::: <variable> • +- <formula expression>

<eva..luated ' f Q ~ u . l a > : := see sect ion 3.1.4.1

3.1.,2 Ex.-ples

y j t 2' + ,sqrt ' (F)

' B V f ' J C I \D "

F ITfs in(C)

• ! ! ,B th,et;l C el se P

F • + G

A '. [ I , J ]

Tay lo r . (F,X,N)

. F

eva1 (X,Y) F (2,3)

3.1 .3 Semantics ,of A r i t h ~ t ~ c t B o o l e a n ; Condit ional , Procedure, Array,

an d Assignntent lQtmulae, '

The proce$s 1>Y which t h ~ value of a 'Formula Algol expression i s

obtained is, explained bY,lneanaof a recurs ively defined function cal led

, '

'-VAL. T h ~ s funct ion dbe snd t lili>pear ,expli,citlY in the, syntax of the source

language, rathe:t;" , i, t iseltec' 'Uted impl ic i t ly a t rUn time on each occasion

in which the 'value of an : e j ( ~ r e S s i ( ) n i s obtained. In the ' de f in i t ion of VAL,.

s' ingle q u o ~ a t i o n : m a , r k s placed, around an expression, e.g'. ' f+g ' , indica te

tha t a fomulacons t ruc t io i lprocess i s to be evoked causing the creat ion

ins ide the computer a, t r ~ : p t i ~ of at data s t ruc ture which represents the

expression. Such data strl ,lctures can be represented in many ways [e .g . t rees ,

Polish pref ix chains, e tc . ] . The choice of such representa t ions i s

implementation dependent and is : no t par t of, the lang:uage i t s e l f . ' As a

fur ther nota t ional convention ' in t h i s p ~ p ~ . ~ , i f Greek l e t t e r s or syntact ic

c l a s s ~ , s are used ins idequqte ; marks, they are non-se l f - re feren t ia l .

Page 12: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 12/53

- 5 -

Formula Algol is a s t r ic t extension of Algol 60 with regard to

values and types. Exactly as in Algol 60, each value has an associated

type. In the explanation of the function VAL below, th e association

of a type with a value i s given explici t ly by writing an ordered pair

of the form «type>, <value».

Formal definition of VAL(E) = (TYPE (E) , VALUE(E».

1. E i s a constant which is either a <number> or a <logical value>.

VALUE(E) is the conventional value of a number or

a logical value (identical to that given by the

Algol Report [1])

TYPE(E) is set to integer i f the" number is an <integer> [1];

i t is set to i f the number is a <decimal number> [1];

i t is set to Boolean i f E is a <logical value> [1].

2. E is of the form • <identifier>

TYPE (E) = Symbol i f th e <identifier> was declared of type

symbol, otherwise TYPE(E) = form

VALUE(E) = '< identif ier> ' . This means that an atomic name

is constructed inside the c o m p u ~ e r .

3. E is a variable

TYPE (E) = declared type of E

VALUE (E) = value of the last expression, say F, assigned to E

by an assignment statement or by an extraction

operation (c.f . section 4.1.2)

Such assignments are legal i f and only i f given E f- F. There is an

arrow in the following graph from TYPE(F) to TYPE(E):

Page 13: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 13/53

- 6 -

4. E is a function designator . Say P(xl, . • . ,xn

)

TYPE(E) == the. type that precedes the procedure

heaqing in the declaration of P.

VALUE (E ) == th e va'lue produced by .th e ca l l of the

procedure P with actual parameters:

VALtJE(xl

) , ••. ,VALUE (xn

) , a s defined

in thE7 Algol report .

5. (Case I) E is a binary expression of the form A <op> B where A and B

T

are formula expressions and

<op> .. . - +1-1* 1/ It t<l!;; I> 1= IllV I" I ~ I ~ TYPE (E) is defined by th e following table:

pe (A)real i n t e g ~ r Boolean

real TI TI error

integer TI T2 error

Boolean error error 1'3I

form T4 T4 T5

form

T4

T4

TS

form

where

. teal

TI=.. Boo lean.

·error .

T2==

T4-t::r

TS={;:::r

i f <op> is a numeric operator

i f <op> is a relat ional operator

otherwise

i f <op> is either a numeric or relat ional operator

otherwise

i f <op> is a logical connective

otherwise

Page 14: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 14/53

- 7 -

I f TYPE(E) = real , integer, or Boolean then VALUE (E) = is the

number or logic value obtained by carrying out the

operation <op> with arguments VALUE(A) and VALUE(B).

I f TYFE(E) is form, then VALUE(E) is 'a < o p > ~ ' where Of is VALUE (A) and S is VALUE (B).

(CASE I I ) E is of the fonm A . <op> B

TYFE.(E) ,= fonn

VALUE (E) = 'a <op> ,

Where a = VALUE(A) and S = VALUE(B).

Here we observe that the use of • <op> automatically causes, in a l l

cases, the construction of a fonmula and prevents actual arithmetic or

logical operations from being carried out.

6. (Case I) E is a unary expression of the fonm <opt> A where A is any

formula expression and <opl>::= sin/cos/exp/ln/sqrtlarctanlsignlentie,rl

-,I+I-Iabs

T Y P ~ ( E ) is defined by the following table:

T

sin,cos,exp sign abs

ype(A)In,sqrt, ent ier + -,

-

real real integer real error

intezer real integer integet error

Boolean error error error Boolean

form form form form form

I f TYPE(E) is real , integer, or Boolean then VALUE(E) is the number or

logical value obtained by carrying out the operation <opt> with argument

VALUE(A). I f TYPE(E) is form then VALUE(E) is the expression '<opt> a '

where Of = VALUE (A).

(Case I I) E is • <opt> A

TYPE(E) = form

VALUE (E) = '<opt> Of' where Of = VALUE (A)

Page 15: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 15/53

- 8 -

Examples

Suppose that at a certain point in a source program that F and G have been

declared of . t y p e ~ , that X and Y h¢lve been declared of t y p e ~ , that

X has been assigned the value 3.2, that Y has been assigned the value 2,

that F has been assigned the value GiS, and that G has as i ts value i t s

.own name . . Qonsider the following assignment statements:

a) X (X + y) t 2 ;

b) F 3 X sin(G) + (F + X) t Y ,;

c) F SQRT(F) ;

In statement (a) a ll variables are numeric. Thus the arithmetic expression

(x + Y) t2 i s evaluated numerically using the current v3.lues of X and Y and

the resul t (27.04) is stored as th e value of X. In statement (b), th e value

of F becomes the formula expression '3)( sin(G) + (GiS + 3.2) t 2' . Finally,

statement (c) replaces the value of F by a formula consisting of th e SQRT of

i t s current value, viz. 'SQRT (3X sin(G) + (GiS + 3.2) t2) ' . I f i t is

desired t·o· reassign the name 'F ' to be the value of F, one may execute the

assignment statement F F. In general, we may use . F anywhere as a

. primary in any formula expression in which i t is desired to refer to th e name

rather than th e value of F.

7. E is a c6nditionai formula of th e form

. i f B then A else C

TYFE(E) = form

VALUE(E) = ' i f Ol ~ l s e y '

where = VALUE(B), Ol = VALUE(A), and y = VALUE(C), furthermore i t is

required TYPE(B) = form or Boolean, otherwise an error will resuit .

The c o n d i t i 6 n ~ 1 action represented by this formula can be executed by

applying the eval operator to VALUE(E) (see section 3.1.4) .. Under evalua-

t ion, i f eval f3 is then the resul t is eval Ol; i f eval f3 is false then

th e resul t is y, otherwise the result is the conditional formula

Page 16: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 16/53

- 9 -

' i f P then ex else y ' where p = VALUE (eval S) and where e x , ~ , and ya re

given above.

8. E is a procedure formula of the form E = A • (Xl

,X2

, . • . , Xn)

TYPE (E) = form

where

Example

VALUE(E) = 'A • (111,11

2, ••• , 11n)'

A is the name of a declared procedure, and

Xl

,X2

, . . • , Xn are formula expressions.

Consider th e assignment statement

F. Taylor . (G,X,N)

where F,G,X, and N are of t y p e ~ . Executing this statement causes the

construction of the formula 'Taylor . (111

,112

,113) ' where 111 = VALUE (G) ,

112 = VALUE (X) , and 113 = VALUE(N), and this procedure f o r m u l ~ , stored as the

value of F, represents a postponed procedure cal l . Applying the eva1 operator

to F causes. the procedure Taylor to be called with an actual parameter l i s t

(eval 11 1, 11 2, eval 11 3 ) where the result of the procedure cal l (which

p r o c ~ d u r e m u s t be a function designator, i .e . must have a value) becomes th e

value of the expression eval' F. Procedure formulae are the means by which

representations of procedure calls may be used in .constructing formula data

structures. I f a normal function designator is used as a primary in the

construction of a formula, the value resulting from th e cal l of the function

designator is used in the construction of the formula instead of the formula

representing the procedure ca l l . E.G., F Taylor (G,X,N) ; causes the

procedure Taylor to be called with actual parameters G,X, and N and causes

the resl;11ting value to be stored in F.

9. E is . an array formula of the form

Page 17: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 17/53

where

"'Example

- 10 -

TYPE (E ) = !£!!!

VALUE(E) = 'A [11 l,il

Z' ••. , 11n]'

A is name of a declared array, and

Xl,XZ

' •.• , Xn are formula expressions.

Executing the assigrtment statement

F <;-A • [I ,J ,K] ;

causes th e construction of the formula fA [11l

,11Z

,113] ' where 111 = VALUE(I),

1 1 ~ = VALUE(iiJ), and 113 = VALUE(K). This formula represents a postponed

array access of th e array element A [I ,J ,K]. Applying the eval operator

to F with integer values for I , J , and K (see section 3.1.4) causes the

execution of the array access. I f a formula is constructed using A [I ,J ,K]

as a primary, then the value of the subscripted variable A [I ,J ,K] is used

in i t s construction. I f , however, a formula representing the subscripted

variable ; i t se l f (in contrast to i t s value) is desired as a primary in a

formula, then the corresponding array formula A • [I ,J ,K] must be used.

An i:mportant application of array formulae is the generation of names

dynamically at run-time. Upon entrance to a block containing the declaration

form ar;ray A[l:N] ; N array elements are created and these become available

as names of storage locations for, use in the construction of formulae internal

to that block. 'Furthermore, the names of these storage locations may be used

in the construction of formulae without any values having been stored into

them. Later, values may be assigned to these locations and by means of the

evaluation process, the values may be substituted for occurrences of th e "names

of the' iocations.

Page 18: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 18/53

- 11 -

10. E is an as,sigmnent formula of the form

Example

A • B _

TYPE(E) ~ " ' f o r m ;

VALUE (E) = A +-" 'where e =VALUE (B)

Consider th e assigmnent statement

F G. f- A + B ;

where th e type of F is and where the types of G,A, and B are any

type other than symbol or Boolean. Executing this statement causes

the construction of the formula 'G ~ a ' where a = value(A+B), and

causes this formula to be assigned to F as a value. Applying th e eva1

operator to F causes eval (a) to be stored as the value of G, and,

additionally, the value of the expression!:'y!! F becomes eval (a).

3.1.4 Evaluation Rules and Evaluated Formulae

3.1.4 . 1 Syntax

<evaluated formula> ::= eva1<variable> I

eva1 <bouuq v ~ r i a b l e l ist> <formula expression> <value l is t> I

'subs «formula expression l ist» <formula E!xpression>

<value l is t> I

replace «formula expression»

<value list>. : := «actual parameter l is t»

«the mark "<" > <variable> <the mark ''>'' »

<bound variable l ist> ::= «formula expression l i ~ t »

«the mark "<" > <variable> <the mark ''>'' »

<formula expression l is t> ::= <formula expression>

<formula expression l ist>, <formula expression>

Page 19: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 19/53

- 12 -

3.1.4.2 'Examples'

eval ( X . Y ~ Z ) ~ ( 3 , 4 , 2 ~ 5 ) " '." subs,.(X,Y) f . , ( A . [ N l ' : + ' 6 ~ B . ( M ' , Q ) / T )

replace (F)

3.1.4.3 Semantics

We may think of formulae as abstractions of computations. By manipulat

ing formulae, we alter' , th e computations they represent. At some point in

the, exetuti,on Qf, a program,' we may wish to carry out the computation

represented by a formula. To do this ,we could substitute values for

occurrences of variables appearing by name only in a fOL"'IIlula, and these

values will he combined according to the computation expressed by the formula

resulting in an evaluated formula. In order to accomplish'" the above, we

have the e{raloperator.

I f we have a formula c o n s i s t i ~ g of names of formula variables joined

by arithmetic operators, then, i f we assign each of the formula variables

a numerica.l "alue, the resul t of the evaluation of the formula will ,be a

number. Hence, the evaluation of an arithmetic formula by complete substitu-

tion 0,£ numbers for fOr'$.ulavariables is a computation carrying the se t of

numbers substi tuted into' a number. Analogously, substi tut ion of Boolean

va.lues 'for formula variables in a Boolean formula produces a Boolean value.

On th e other hand,we need not substitute arithmet:i,.c or Boole'an values

for formula variables, but rather , we can substitute other formulae. lhis ,

in this case, evaluation of the formula, instead of producing a single value,

expands i t to an enlarged formula. Hence, eval may be used to construct

formulae.

A third use of is that oJ; producing' t r ivia l simplifications in a

formula without altering i t s value and without substitution. This is done

Page 20: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 20/53

- 13 -

according to the following table:

Simplif icat ions

A t 0 1

A t 1

A t - l ~ l/AA t - n ~ l / A t n

A / 1

A / ( - l ) ~ -AA / ( - n ) ~ - (A/n)

o / A 0

(-n) / A ~ - ( n / A )

x V t rue true

X 1\ t rue X

X V false " ~ X X 1\ false false

of eval

A X 0 - - ~ 0

A X 1cOImnula L ive

A X -1-> -A

A X - n ~ -(A X n)

A + o

A + (-n) A - n

0 + A

(-n) + A A - n

A - o

A - (-n) A + n

0 - A ~ - A (-n) - A ~ - ( n + A)

conunutative.

Whenever an expression contains two numeric (Boolean) arguments joined

by an ari thmetic ( logical) operator , they are combined by eval into a

numeric (Boolean) resu l t according to the operation expres3ed by this

operator .

A f ina l use of eval is to carry out th e array access or procedure ca l l

indicated by an array formula (see section 3.1.3) or a proc-edure formula

(see section 3.1.3), or to carry out the assignment of a valt.ie or th e choi.ce

of a value indicated by an assignment formula (see sect ion 3.1.3) or a

condi t ional formula (see sect ion 3.1 .3) .

These uses of eval are usually combined. 1hus evaluation of a formula

may produce par t ia l expansion, and some t r iv ia l s implif icat ion simultaneollsly.

Note: All subst i tut ions are carr ied out simultaneously.

Page 21: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 21/53

- 14 -

I . The substi tution operation

The operation subs, which evokes a subst i tut ion process, is defined

as follows:

Consider a statement of the form

Then

(1)

where n 1 and m 1.

(a) F must be a formula expression.

(b ) I f TYPE(F) is numeric or Boolean or i f VALUE (F) , is a numberor logical constant, then the effec t of 1 is precisely thatof D F.

(c) I f TYPE(F) = form and VALUE(F) is a formula, then D wil lhave the value obtained by substi tuting Y. for each

occurrence of X: in a copy of VALUE(F), provided VALUE(Xi

) is

an atomic formula variable. This subst i tut ion is performed

for each i m.

(d ) Yi

may be an expression of any type except symbol.

I I . The evaluation process

The evaluation operator eval is defined as follows: Consider a

statement, of the form

Then rules (a), (b), (c) , and (d) above apply without change. In addition,

th e resulting formula is simplified according to the table above and

executing eval F where F is an assignment formula, a procedure formula or

an array formula, respectively, causes the assignment to be executed, th e

procedure to be called, and the array element to be accessed respectively.

When evaluating a conditional formula, only i f the Boolean formula in

the i f clause yields a Boolean value wil l the conditional action represented

Page 22: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 22/53

- 15 -

by the formula be executed.

III . The function replace

The function designator replace(F) where F is a formula expression

produces a formula which is obtained from F by replacing every atomic

variable in F by i ts currently assigned value and by applying eval to the

result . The atomic variables used in the formula F must be declared

either locally or globally to the block in which replace(F) is executed.

3.2 Symbolic Expressions

3.2.1 Syntax

<symbolic expression> ::= <variable>I < f u ~ c t i o n

designator>

<selection expression> I <value retr ieval expression>

<the mark "<" >. <symbolic expression> <the mark ' ~ I I >

3.2.2 Examples

S

Select (L,N)

3 rd of S--olor (apple)

< S >

« S »

last N of indexlist (M th of S)

3.2.3 Semantics

A symbolic expression is a rule fo r computing either a single symbol

or a l i s t as a value. This occurs according to the following rules.

1. I f S is a variable declared of type symbol, the value of Sis the current contents of S. When an identif ier is

declared of type Symbol, i ts contents are ini t ial ized to

contain the name of S (this is no t true for subscripted

variables). Thus, after declaration and unt\l destroyed

by an assignment statement, by a push down statement,orby an extraction, the value of S is th e name of S. Execut-

ing the special assignment statement S .S restores th ename of S to be the value of S. I f a l i s t has been stored

as the contents of S by an assignment statement, then the

value of S is the l i s t . I f the contents of S has been

Page 23: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 23/53

- 16 -

pushed down or popped up th e value of S is the symbol

or l i s t a t the current top of the push down stack. I f

the contents is empty, the va' lueof S i s th e symbol ni l .

2. I f S is a function designator result ing from the declarat ion of a symbol procedure, the value of S is that assigned

to the procedure identif ier by executing the body of theprocedure declaration using actual parameters given in th efunction designator cal l .

3. I f S is a select ion expression (see section 3.2.6) , then

th e value of S is a part of some symbolic data structureselected according to th e select ion rules set forth insection 3.2.6.

4. I f S is a value re t r ieval expression , then the value of Sis a' function of an ordered pair of symbols (T, U) consisting of the value l i s t associated with the. attr ibute U onthe description l i s t attached to T (see section 3 ~ 2 . 5 ) .

5. I f S is a symbolic expression of the form <T>, where T i s

a symbolic expression, the value of T is f i r s t computed

and i f the result i s a single atomic symbol, say 'V', the

value of S is the contents of 'V' otherwise th e resul t is

a run-time erro·r. The angular contents brackets may be

nested a r b i t ~ a r i ~ y many times to provide arbi trari ly manylevels of indirect access.

The sub-language for l i s t processing is so arranged that anywhere an atomic

symbol occurs in a statement or an expression i t may be . replaced by a

symbolic expression which when evaluated yields an atomic symbol as a

resul t . Further, anywhere a l i s t may occur in a statement, i t may be

replaced by a symbolic expression which when evaluated yields a l i s t as a

resul t .

3.2.4 Lists

3.2 .4 .1 Syntax

<lis t> ::= <l i s t element>I

<list>, <list,element>

<l i s t element>::= <expression> I <l i s t expression> <description l is t>

<symbolic expression> <description l ist>

<l i s t expression> : := [<list>]

<expression> ::= <arithmetic expression> I <Boolean e x p r e s s i o ~ I

Page 24: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 24/53

- 17 -

<formula expression> I <formula pattern> I

<symbolic expression> I <l i s t pattern> I <l i s t expression>

3.2.4 .2 Examples

[X + sin(Y), false, [A,B,C], F - G]

[A,E,I,O,U]

3.2 . 4.3 Semantics

Symbols may be concatenated into a l i s t by writing them one af ter

another, and by separating them with commas. This l i s t may be assigned as

th e contents of another symbol by executing an assignment statement. E.g.

Vowel ~ [ A , E , I , O , U ] ; In addition to symbol variables, any expression

except a designational expression may be written as an element of a l i s t

and i t s value wil l be entered. For example, le t X,Y, and Z be formula

variables, le t A,B, and C be Boolean var iables , . le t U,V, and W be real

variables, and le t R,S,and T be symbol variables. Then the assignment

statement

S f - [X + sin(Y), 3 + 2XU, i f B then R else T, [R,T,R], -36] ;

when executed causes each expression on th e r ight to be evaluated,. and th e

l i s t of values to be sotred into the contents of S. Automatic data term

conversion resul ts from storing non-symbolic values into l i s t s •. The second

from th e las t item in th e above l i s t is the quantity [R,T,R]. This becomes

a sub1ist of the· l i s t stored into S. Hence, the expression stored into S

i s , in real i ty, a l i s t structure. It is further possible for cer tain of the

elements o fa l i s t to bear local ·description l i s t s (see section 3.2.5.3) .

3.2.5 . Description Lists

3.2.5.1 Syntax

<description l i s t> ::; / .<attr ibute value l ist>

Page 25: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 25/53

- 18 -

<attr ibute value l ise> ::= <attr ibute value segment> I<attr ibute value l is t> <attr ibute value segment>

<attr ibute value segment> ::= [<attribute> : <list>] I[<attribute> : <empty>]

<value re t r ieval expression> ::= <identifier> «symbolic expression» Ithe <attr ibute> of <symbolic expression>

<attribut.e> ::= <symbolic expression> I <formula expression>

3.2.5 .2 Examples

Description l i s t s

/[ types: mu, pi, rho][color: green][processed:

/ [propert ies: continuous, different iable]

Value Retrieval Expressions

color (apple)

the ancestor of th e lef t relat ive of <6>

3.2.5.3 Semantics

A description l i s t is a sequence of at tr ibutes and values. An

at t r ibute may be any atomic symbol or any formula. The value of any type

of e ~ p r e ~ s i o n except a designational expression may be used a s a value.

Each at t r ibute is followed by a l i s t of values associated with i t . This

value l i s t may contain more than one member, i t may contain only one

member, or i t may be empty. A description l i s t may be attached to one of

three types of objects:

1. A variable declared of type symbol for which there are

two cases (a)' global attachment, and (b ) local attachment.

2. A variable declared of type form.

3. A subl i s t of a l i s t .

Assignment statements are used to construct and to attach description l i s t s .

For example, assuming that a l l variables involved have been declared of type

Page 26: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 26/53

- 19 -

s ~ b o l , the statements

S ~ / [ t y p e s : mu, pi, rho][ancestors: orthol, para5][color: green] (1 )

T ~ [ F , A/[mark:l], B,C, A/[mark:2], D,E] ; (2 )

assign respectively a descript ion l i s t to S and a l i s t as the contents of

T. The description l i s t attached to S is globally attached meaning that

i t is permanently bound to S for the l ifetime of the variable S which

l ifet ime is de·termined· by the ALGOL block structure in which S occurs. In

the l i s t assigned as the value of T, th e symbol A occurs twice in the second

and fourth posi t ions. The description l i s t s attached to these two separate

occurrences of A are attached locally meaning that the separate occurrences

of a given atomic symbol within a l i s t have been given descriptions which

in terfere neither with each other nor with th e global descript ion l i s t

attached to A i f such should occur, and that th e at t r ibutes and values of a

given local description l i s t are accessible only by means of symbolic

expressions accessing the part icular occurrence of th e symbol to which the

given local description l i s t is attached.

In th e following examples, suppose F is a variable declared of type

form and that a l l other variables involved are variables declared of type

symbol.

F ~ / [ p r o p e r t i e s : continuous, different iable] ; (3 )

V ~ [ A , [B,C]/[processed: ~ ] , A , [B,C]/[processed: false],A] (4 )

In example (3), a descript ion l i s t is attached to a formula. In example (4),

the l i s t assigned to be th e contents of V has two ident ical sublists [B,C]

in th e second and fourth positions having different local descript ion l i s t s ~

Value l i s t s ' s tored in description l i s t s are retrieved by means of value

. re t r ieval expressions. To accomplish re t r ieval two arguments must be

supplied:

Page 27: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 27/53

- 20 -

(1) an attribute confj;isting of an atomic symbol or a formula, and

(2) an atomic symbol or a posi t ion in a l i s t structure having adescription il$t.

The at t r ibute ' is t h e n ' , : l o ¢ ; ~ t e d ' the < l ~ s c r i p t : j . o n l i s t i f , i t is present

and i t s .g,ssociated value l i s t ~ i f a ~ y , becomes th e value of the retrieval

'expression. I f there ' is no description l i s t , or 1f there is a description

l i s t but th e attr ibute does not appear on it, or i f the at t r ibute does

appear on it but has a n ~ e m p t y value l i s t , then the value of the retrieval

expression is the symbol Ilil.. Thus, in examples (1) and (2) above, the

value re t r ieval e x p r e s s i 0 1 l , s ~ o l o r (.8), mark (2 EE . of T), and mark (3 rd of T)

have th e values green, 1, and n ~ l respectively. The 'construction, the color

of .8 , accomplishes the same 'function as color ( .8) but is sl ight ly more

versati le in that any symbolic or formula e x p r ~ s s i o n may be used to calculate

the at t r ibute whereas or, . lyldentif iers may be used for th e at t r ibute in th e

form <identif ier> «symbolic expression». Thus, for example, th e expression

th e 3 rd of types(.8) of <P>. is a legal value re t r ieval expression whose

at t r ibute is calculated by selecting the third element of the l i s t which is

, the value of the expression types (.S). In example (1) above, , i f i t is

desired, to access at t r ibutes ,of, the global description l i s t of th e second

element A, instead o £ a ~ c ' ( 2 s s i n g only i ts local description l i s t , then the

element must be selected ,by means of a selection expression, stored into a

variable, and an indirect a'ccess of the global description l i s t performed.

E.g.' X 2 nd of T; p ~ . mark (X); are two statements which, in th e case of

example (2) 'above, extract the name 'A ' and store i t as the value of X,'and

which then access the value l i s t associated with th e at t r ibute 'mark' on the

global description l i s t of the value of X ( ; . e . , the global description l i s t

of A) . The resu l t is stored in 1> • .

Page 28: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 28/53

- 21 -

3.2.6 Selection Expressions

'3 .2 .6.1 Syntax

<selection expression> ::= <selector> of <symbolic expression>

<ordinal suffiX> ::=!!I

ndI

rdI

th

<ordinal selector> ::= <arithmetic primary>W<ordinal suffix> 1 las t

<elementary position> ::= <ordinal selector.> I <ordinal selector>

<cla.ss name> I <ordinal selector> <expression>

<ordinal selector> <augmented type> I <ordinal selector.> integer

<arithmetic primary>

<position> ::= <elementary position> I <arithmetic primary>w

<ordinal suffiX> before <elementary position>

<arithmetic primary>U<ordinal suffix> af ter <elementary position>

<selector> ::= between <position> and <position> 1 a l l af ter <position>

a l l before <position> I f i r s t <unsigned integer> Il as t <unsigned integer> I <position> I a l l <expression>

i l l . <augmented type> a l l <class name>

<augmented type> ::= real integer I Boolean

subl is t I text I atom I an y

3.2.6.2 Examples

3 rd of S- -las t of S---

  t h r e a l of S

las t sub1ist of S

las t [ ~ , B , C ] . of S

5 th (I tr igfunction I) of S

N th before l as t Boolean of S

a l l symbol 6f S

las t 3·of S

form symbol

Page 29: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 29/53

- 22 -

3.2.6.3 . Semantics

Selection expressions are formed by composing selector operators with

symbolic expressions. A symbolic expression is f i r s t evaluated producing

a symbolic data s tructure as a value. A selector operator is then applied

. to the result ing symbolic data s tructure to gain access to a part of i t .

Assume f i r s t that the symbolic data structure , S, on which a selector

operates is a .simple l i s t . Then

1. An ordinal selector refers to an element of this l i s t e i ther by

numerical posi t ion, i . e . , the n th element, or by designating

the l a s t element. E.g. 3 rd of l a s t of S.

2. An elementary posi t ion refers to an element of th is l i s t bydesignating i t (a) as the n th or las t instance of an augmented

type, e .g . , n th real , las t S l : i b l i s ~ b ) as the n th or l a s t

instance of an-;xpression, e .g . , n th (F + G), las t [A,B,C] ,

(c) as the n th or las t instance of-a member o f ~ l a s s , which

class may be defined as consist ing of any arbitrary Boolean

t e s t on an element (see section 4.2.6), e .g . , 5 th <Itr igfunct ion/) ,

las t (Ivowell), Cd) or as the n th or l a s t , i . e . , by ordinalselect ion.

3 . A position refers to an element of th is l i s t e i ther by designating

i t s elementary position or by designating i t as the n th before

or th e n th af ter some elementary posi t ion.

4. A selector refers to an element by i t s position or else designates

one of the following sublis ts of the l i s t

a) The sublist between two posi t ions , e .g . , between 3 rd and 7 th

of S.

b) The subl is t consist ing of a l l elements before or af ter a given

posi t ion, e .g . , a l l af ter 3 rd symbol of S, a l l before l a s t

real of S.- -) The sublis ts consist ing of th e f i r s t n elements or the l a s t n

elements, e .g . , f i r s t 3 of S, las t k of s.

d) The sublis ts consist ing of ( i) a l l instances of a given expression, e .g . , a l l F of S, <ii) a l l instances of a given augmented

type, e.g . , -aI1 r ; a l of S, ( i i i ) a l l instances of elements

which are members of a-given class , e .g . , a l l <Itrigfunction/)of S. The elements of th e subl is ts so ~ o m p o s e d occur in the

same order that they occur in th e l i s t from which they areselected.

Page 30: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 30/53

.. 23 -

Selectors maybe compounded to access subl1sta end t h e t ~ e ~ n t s . Suppose

the statement S 4 - {At '(X,K, [AtA]., Xl. A) has been executed. then the

expression 2 .!!2 of S is a l i s t valued symbolic expression with the l is t

[X,X, [A,A], X] as value, whereas the expression 3- rd of 2 nd o£ S has the, ...-.-.......... ,

l i s t [A,A] as va.lue, and whereas the exp:ressiQu 1 4 S ~ 2.! 3 ..2! 2 S

has the single atomic symbol A as value.

I t is possible for selectors to refer to elements or sublis ts which do

not exis t . For .example, suppose the statement S . r IA,B,C]; "has been

executed. Then the expression 5 th S refers to an element which doesn't

exist . The value of such an e ~ p r e s s i o n l'S, thSiS11ll.bo!.t'!-il. .similarly, the

expression f i r s t 5 El s r-efers to a s u b l ~ . s t which doean' t exist . The value

of this 'expression i a t he 11st [ A , a : l C ~ ~ ~ . ! ) n i . l 1 . Generally, the rule i s

(1) if a selection ex:presston refers to a single element which doesn' tel t ist"

the value of the expresaion is the syUibol!!!!.t and (2) i f a selection

expression refers to a sublistrequlr:e6 toconta1n more elements tha t ar'e

a.vailable in the l i s t ',structure being ,acce-ased. then the symbol!!!.! i s

repeatedly appended to the end of t h ~ insuffic ient structure until it is of

requisi te length.

4. Predicates for For,mulae and List Structures

4.1 Formula Patterns

4.1.1 .Syntax

<formula pattern> ::= <formula expression> == <formula pattern s t rqctur?>

< ~ o r m u l a expression> .;» <formula pattern.structure:>J

<extrac tor> <formula e.xpression> »<ex t r a c or> <formula. pattern .

structure>

<extrac tor> : :.= <variable> :

Page 31: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 31/53

- 24

<formula pattern structure> ::= <a formula exp;ression i1iJ,. which some

of the primaries may have been replaced by pattern primaries

and some of the operators may have been replaced by operator

classes> t

<formula pattern primary> ::= <type> I I any I of «variable»

Ofi «procedure identif ier» I «formula pattern structure» I<e-x:t.ractor> <formula pattern. primary>

<operator class> ::= <the mark n·f',> <operator) ~ l f l ? , s ~ a m e > <the mark" I ,>

<operator class name> ::= <variable>

<operator class assignment> ::= <operator class name>

/[operator: <operator l is t>] <operator attr ibute li.st>

<operator l is t> ::= < o p e ~ a t o r > I <operator l is t> , <operator>

<operator attr ibute l is t> ::= <empty> I [ ~ : <logical value l is t>] I[index:<variable>] I [ ~ : < l o g i c a l value l ist>][index:<variable>]

<logical value l is t> ::= I false I <logical value l is t> , I<logical value l is t> , false

4.1.2 Semantics

A computation may construct a formula Whose structure cannot be

predicted in advance or a si tuat ion may arise in a program where i t is

desired to discriminate among various formulae in a given class depending

on their various properties. Fo r this a mechanism is needed to determine

preCisely the structure. of any given formula. Formula patterns are used for

this purpose and they constitute a set of predicates over the class of

formula data structures. These formula patterns are suffic ient in the sense

. .

t This is a short description of what could be a formal syntactic statement.

Page 32: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 32/53

- 25 -

that Whatever constructions are used to create a formula, th e process may

be reversec;l by the choice of a sequence' of predicates. Furthetmore, a

given formula p a t t ~ r n may be u ~ e d to represent a class of possible formulae,

and any fOWlulamay be tested for membership in this class.

In th e definit ion of a formula pattern, a formula expression, F, is

compared wtth a formula pattern structure, P, to determine one of two things

(1) correspond.ing to the construction F==P, whether ~ h e expressi.on F is an

exact instance of th e formula pattern structure P or , ' (2 ) corresponding to

th e construction F»P, whether th e formula expression F contains an instance

of the formula pattern structure P .Bo th constructions F==1> and E»P are

Boolean expressions having values true or false.

The Construction F==P

The formula expression F is defined recursively to be 9-n exact instance

of the fort1lulapattern structure P as follows:

1. I fP i s a type word: inteser, Boolean, form, or symbol,then F==P is true i f and only i f the value of F is a rea l number,an integer, a logical value, a formula, or a l i s t structure

respectively.

2. I f P is the reserved word atom, then F==P is true i f and ot;lly i f

. the value of F is either a-n-umber, a logical-va:Iue, or an atomic

formula name., !"

3. I f P is the r e ~ e r v e d word any, then F===P is always true.

4. I f P is the construction of «varia.ble» where the variable, say S,

m4st be. d e c 1 ~ r e d of type-Symbo1, and where S has been assigned as

a value, a l i s t of formula pattern structures, say (Pl

,P2

, . .• , PnJ,

then: F=:;;;P is i f and only i f F==P1 V F==P2

V ••• V F==Pn is

.\ true.

5. I f P is the construction of «procedure identifier» where th eprocedure ident if ier names a Boolean procedure with one formal

parameter s ~ e c i f i e d of type form, for exantple,. Boolean procedure

. B'(X); fo;cm X; <pr9cedure body>, then F==P is true i f and only i f

, the procedure cal l B(F) y 1 e l d ~ :the value true •.

Page 33: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 33/53

- 26 -

6. I f P is of th e form Al <oP>l Bl

, then F==P is i f and only

i f (a ) F is of th e f O ~ i m A2 < o P ~ 2 B2

, (b ) A2==A

l, (c) B

2==B

l,

and (d ) i f <0P>1 is a single operator then <0P>2 must be

identical to <oP>l whereas i f <oP>1 is an operator class, then

<op>Z must be a member of <oP>l as defined b e 1 0 w ~ 8imilarly,

for unary operators, i f P is of the form <oP>l Bl

, then

F==P is i f and only i f (a) F is of the form <oP>2 B2 and

conditions (c ) and (d ) above are true.

7. I f respectively P is of th e form(a) <array identifier> [8

1,8

2, . . • , 8

n]

(b ) <procedure i d e n t i f i e r ~ . [81

,82

, . . • , 8n

]

(c) <variable> • 81

(d ) . i f 81 then 82 else 83

where 81

,82

, .•• , 8n

are formula pattern structures, then

F==P is true i f and only i f respectively

(a) F is an array formula with the same array identif ieras P and with a subscript l i s t whose successive

elements are instances of 81

,82

, . • . , 8n

.

(b ) F is a procedure formula with th e same procedure identif ieras P and with an actual parameter l i s t whose successive

elements are instances of 81

,82

, . • . , 8n

(c) F is an assignment foomu1a with the same l e f t part variableas P and with a r ight hand expression which is an instanceof 8

1.

(d ) F is a conditional formula of th e form • i f B then C else D

and B==Sl' ,C==82

, and D==83

Extractors

Assume for some P and Some F that F==P is true. I f an extractor is

used in P preceding a formula pattern primary, then the subexpression in F

Which matches the'for.mula pattern primary preceded by the extractor is

assigned as the value of th e variable found to the lef t of the colon in the

extractor.

Page 34: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 34/53

... 27 ...

Operator Classes and Commutative Instances

. Before an operator c l ~ s s is used i,n a fonnula pattern, i t must be

defined. The definition is accomplished by an operatqr class assignment

which assigns to a variable. which must be declared' of type symbol, a

. description l i s t of the form

/[operator: <operator l ist>] <operator attr ibute l is t>

Suppose R is a variable declared of.type symbol for which the following

operator class assignment has been executed:

R /[operator: +, . , / ] ( ~ : false , £alse][inde,x: J]

where J must be a variable declared of type integer and where operator,

and index are reserved words used for special attr ibutes. Let P be

a fonnula pattern structure h ~ v i n g the form

Then F==P' is true i f and only i f (a ) F 'i s of the form A2 <op> 2' B2

,' and

(b) one of the two following conditions hold:

' ( i) 'A2==A

I, B

2==B

I, and <oP>2' is-a. member of th e operator

value l i s t found on the description l i s t of R. In thespecific case above, this l i s t is [+,_,/]. I'

(i i ) B 2 = = A ~ , A 2 = = B l ' and <oP>2 is a member of th e l i s t of

operators obtained from th e operator value l i s t by

deleting those operators whose corresponding logicalvalues, in th e logical value l i s t following th e attr ibutecorom are false. (In th e specific case above, this

reduced operator l i s t is 'the l i s t consisting of th esingle operator +). Thus commutative instances about

+ are considered, but not cOminutative instances about

- , or I. Note that [corom: true, false, false] need not-- --....-appearQn th e description l i s t of R at a l l in which caSeno commutative in,stances of any o p ~ r a t o r will be considered.)

Page 35: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 35/53

- Z8 -

I f F==P is t rue , the integer variable used as value of the attr ibute index

wil l be se t to an integer denoting the position of <op>Z in the operator

value l i s t . (In the specific case above, J is set to 1,Z, or 3 according to

Whether <op>Z was +,-, or / respectively.) The operator <op>Z is stored as

a data term as the value of R. Later the construction I[R]I can be used in

an expression in place of an operator, and th e operator <op>Z extracted

during th e previous matching wil l be used in the construction of the formula

data structure that the expression represents. Alternatively, R may be

assigned any operator by the assignment statement R ~ < o p e r a t o r > ; and I[R]I

may be used in th e same fashion.

The Construction E»P

The formula pattern E»P is true i f F contains a subexpression, say 8,

(Which may be equal to F i t s e ~ f ) such that 8==P is t rue . A recursive process

is used to sequence through the set of sub-expressions of F for successive

testing against the formula pattern structure P. The sequencing has the

properties that i f two sub-expressions 81

and 82

are both instances of P,

then i f 82

is nested inside 81

, then 81

wil l match P f i rs t , and i f neither

81

nor 82 is nested inside the other, then i f 81

occurs to th e r ight of 82

in a l inearized written form of 8, then 81

is recognized before 82

"

The formula pattern A:F.»B:P in Which extractors precede the r ight and

le f t hand sides of the formula pattern has the following meaning. Firs t ,

F.»P is tested.. I f th e result i s ~ , then (a) the sub-expression of F

Which matches P is stored as the value of B, and (b) a formula is constructed

consisting of F with the sub-expression matching P replaced by th e previous

value of B (viz. the value B had before the assignment described in (a) took

place). · T h ~ s formula is stored as the value of A.

4.1.3 Examples

Page 36: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 36/53

- 29 -

4.1.3 Examples

Example 1. Let A,B,X,Y, and Z be declared of type and le t R

be declared of type real . Suppose that the statement

X (- 3 X sin (Y) + (y - Z) / R + 2 X R ;

bas been executed. Consider the statement:

i f X» A: integer X B: sin(form) then Z 2 X B + A ;

Since the pattern X»A: integer X B: sin (form) i s ~ , the assignment

Z X B + A will be executed, assigning as the value of Z th e formula

2 X sin(Y) + 3 because A has the value 3 and B has the value sin(Y).

Example 2. Let X be of type symbol, A,B,Y,M,T,G, and P be of type

and D be of type Boolean. Then executing the statements:

X [real , integer, Boolean] G Y + 8x (M - T) ;

P +- form + A: of (X) X B: form D <E- G==P; causes D to be se t to true because

the pattern G==P is and causes A to be se t to 8 and B to be set to

M - T.

Example 3. Suppose we execute the statements

F <E-2 x(sin (Xt2 + Yt2) + cos (Xt2 - Yt2) / 5; G <E-sin(form) + cos(form)

where a l l variables used 'are of type form. Then A:F:»T:G is a pattern with

value true. The value of T will replace the f i r s t instance of G in F, i . e . ,

the expression sin(Xt 2 + Yt2) + cos (Xt 2 - Yt 2) (this being the f i r s t sub

expression matching the pattern G according to the sequencing pr ior i t ies

defined above). A is assigned the expression 2 X T / 5. 'lhus A is the same

as F with the f i r s t sub-expression of F matching G replaced by the value of T.

Example 4. Assume a l l variables in t h ~ f o l l o w i n g sequence of declara

tions and statements are of type fonn.

Page 37: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 37/53

- 30 -

Boolean procedu:re HASX(F); value F; F; HASX F»X;

G (Xt,2 +3 ) t2 X (Y - 1) ; F ~ A : o f ( H A S X ) X B: (any-I)

T ~ G = = F ' j

Then T is set to ' true, A is set to' (Xt' 2 + 3) t 2, and B is set to Y-I.

Here we se e that any Boolean procedure may be used in a formula pattern to

t es t th e properties of a matching ~ u b - e x p r e s s i o n of a formula. The ful l

generali ty of Boolean procedures is thus delivered.

4.2 List Patterns

4.2.1 Syntax

<l i s t pattern> ::= < ~ y m b o l i c expression> == [<l i s t pattern structure>J IJ

<l i s t expression> == [<l is t pattern structure>J

<symbolic expression> == <l i s t expression> I

<symbolic expression> == <symbolic expression>

<l i s t expression>== <l i s t expression>

<l i s t pattern structure> ::= <l i s t pattern primary>

<l i s t pattern structure>, <l i s t pattern primary>

<l i s t pattern primary> : := $ I $ <arithmetic primary> I <expression>

<class name> I <augmented type> I <l i s t pattern primary>

< d e s c r i ~ t i o n l ist> 1 <extractor> <l i s t pattern primary>

[<l is t pattern structure>]

<extractor> ::= <variable> :

4.2.2 Semantics

List patterns are predicates for determining the structure of l i s t s .

List patterns use th e mechanisms found in COMIT [5 J to tes t Whether a

l inear l i s t is an instance of a certain l inear 'pattern. The l i s t pattern

structure describes the pattern being test.ed for, and is composed of a

sequence of l i s t pattern p ~ i m a r i e s separated by commas. The symbols $ and'

$ n may be used as l i s t pattern primaries with the same significance as in

Page 38: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 38/53

- 31 -

COMIT (viz. $ stands for any arbi t rary number of consecutive arbitrary

elements and $ n stands, for n consecutive arbitrary elements). I f a

symbolic expression ls used as a l i s t pattern primary, i t s value is f i r s t

computed, and if that value is a l i s t , each element of th e l i s t becomes

'one of theconsecut tve l i s t pattern primaries in the l i s t pattern structure.

Other kinds of elements introduced, below may also become l i s t pattern

primaries.

A l i s t pattern compares a l i s t (determined by ei ther (1 ) a l i s t

expression, or (2) a l i s t valued symbolic expression) to a linear pattern

(described by either (1) a l i s t expression, (2) a l i s t valued symbolic

expression, or (3 ) a l i s t pattern structure) to see i f the l i s t is an

instance of the pattern. The l i s t pattern is a Boolean primary with values

true and false and thus may be combined with other Boolean expressions by

means of logical operators.

4.2.3 Examples

Example ,1. Suppose the statement S [A,B,C,D] has been executed,

where a l l variables involved have been declared of type symbol, and where

the values of A,B,C, and D are their respective names. Consider the state-

ment

i f S == [$1 , B, $ ] th en T [T, B] e 1seT [T , la s t 0 f S] ;

Since the contents of S, which is the l i s t [A,B,C,D] is an instance of th e

pattern [$1, B, $] (which is read "a single arbitrary constituent, followed

by a B, followed by any arbitrary number of arbitrary constituents"), the

l i s t pattern S == [$1, B, $] i s ~ . Therefore, T [T,B] is executed,

which has the efrect of appending a B to the end of the l i s t stored as the

value of T.

Page 39: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 39/53

- 32 -As with th e formula pattern structures used both as predicates and

selectors for formulae, l i s t pattern structures may function not only as

predicates but also selectors . The same mechanism ,is used to accomplish

this . I f any l i s t pattern primary in a l i s t pattern structure is preceded

'by a variable declared of type symbol followed by a colon, then the correspond

ing element in the l i s t being tested, in the event there is a match, becomes

the value of that ,symbol variable. The value may be accessed at any la ter

point in the program.

Example 2. As in the previous example, suppose the statement

S [A,B,C,D] has been executed where a l l variables are symbols and where

A,B,C, and D have as values their respective names. Then, executing the

statement

.!! S == [T : $2, V: $2] then S [V, T]

changes the contents of S to be the l i s t ' [ C ~ D , A , B ] . Furthermore, the' contents

of T has as i t s value th e l i s t [A,B], and V has as i t s value th e l i s t [C,D].

4.2.4 Equality Tests

I f we have two symbolic expressions, we may t e s t whether their values

are equal by means of the relat ion <symbolic expression> == <symbolic

expression>. The values of the symbolic expressions maybe single 'symbols,

l i s t s of symbols, formulae, or values of a!?-.y other type. Naturally, i f the

values of. th e two symbolic expressions are non-conformable data s t ructures ,

the result of th e predicate wil l be ,false . Similarly, two l i s t expressions

may be tested for equali ty, as maya symbolic expression and a l i s t expression.

4.2.5 Testing for Types

A single vaiued symbolic expression having a vaiue whose type is unknown

may be used in th e l i s t pattern <symbolic expression> == <augmented type>

in order to determine the type. An augmented type is ei ther r ea l , i n t ege r ,

Boolean, form, symbol, sublis t , or. any.. Here the type text is

Page 40: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 40/53

- 33 -

assigned to any Formula Algol reserved word ante·red in quotation marks as

an element of a l i s t . E.g. , s +- [ 'g ' B, ' ~ ' , C] Where 1 s t of S - -- -. ! ! ! ! i s and ~ 1 " e 3 ~ . 2 ! s === 1s t t : u ~ . The type is true

fo r atomic:. formulae, mnnbers, and logical values, aIld t:.ype anx 1s t rue

. for any arbi trary element not of tyPe symbol.

4.2.6 Testing for Ketnbership in a ,Class

Class Oe.f.lnitions

4.2.6.1 Syntax

<c lass name> ! := (l<symbo1ic expression> J)

<class primary> : := <class name> «c l a s s express1on>]

<class secoI\4s..-P : := <claS:S primary> l - <C146B primary>

<elaa·s factor!> :'1::: <class secondary> J <class f'Qctot> A <class secondary>

<class expression> ::= <class fac tor> f <class expression> V <class factor>

<class defini t ion> : : ~ l e t <class name> = [<foanal parameter>

<the ma:rk "ftl> <Boolean expression>] f <class name> =

<c l ass expre·8s1on>

H.2.6.2 Semantics and Examples

, Sets may be defined by means of c lass definit ions. For example,

suppose the sta tement V +- [A.,E,I,O,U] has been executed. Then the statement

le t <lvowe11) = [X I Among (X,V)] ; defines the se t of a ll vowels where

Among(P,Q) i s a Boolean procedure which i s t rue 1f P i s an element of the

l i s t contained Q, and false otherwise . Suppose. nowt tha t having sometime

previously executed the. statement S [A,B,C], we execute the sta tement

.!! 1 s t of S == ( I v ~ w e l l ) de l e t eS ;

The l i s t pat te rn 1 of S == (Ivowell) w i l ~ .be .evaluated by f i r s t computing

the value ox the expression 1 !!! of S, which i s the symbol A, an d second by

Page 41: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 41/53

- 34 -

substi tuting A for th e formal parameter X in the class definit ion of

(Ivowell). This resul ts in the Boolean'procedure Among (A,V) being executed,

the value of which is t rue. Thus, A is a member of the class <Ivowell),

and thel i s t

pattern 1 of S==

</vowell)is

t rue. This causes the

statement delete S to be executed which erases th e value of S.

Class definit ions may consist .of Boolean combinations of other defined

classes . E.g. , le t (IAj) = <IBI) /\ ( ICI>; is legal provided class

(IBI) and class <ICI) are elsewhere defined. Another example of a class

definition would be le t <Iemptyl) = [Xl fa l se ] ; This defines the empty'

se t . Note: Any arbi t rary Boolean expression including a Boolean procedure

ca l l may be used to define a class . Thus the fu l l generali ty of Boolean

procedures is delivered.

Class definit ions may be used as l i s t pattern primaries in l i s t pattern

st ructures . When this is d'one, the element matching the class definition

is tested for membership in the class. I f th e resul t i s ~ , the l i s t

pattern structure continues to be matched against the l i s t being tes ted. I f

the resu l t is false, the l i s t pattern structure fa i ls to match the l i s t being

. tested. E.g. S == [D, <Ivowell), $] is a legal l i s t pattern which tes ts

the l i s t which is the value of S to see i f i t is of the form D, followed by a

vowel, followed by an arbi t rary number of arbitrary consti tuents. Similar ·to

formula pattern structures, l i s t pattern structures may be stored as th e

value of a variable for use in l i s t patterns. E.g., the statements

S [$1, B, $] ;

to the statement

T [ ~ , B , C , D ] ;

i f [A,B,C,D]

i f T == S then to exi t

[$1, B, $] then to

are equivalent

Page 42: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 42/53

- 35 -

5. Other Kinds of Statements and Expressions

5.1 Push Down and Pop Up Statements

5.1.1 Syntax

<push down operator> ::= I <push down operatot>

<pop up operator> ::= t , <pop up operator> t

<push down s t a t e m e n ~ ::= <push down operator> <sy,mbolic expression>

<pop up.statement> :.;= <pop up operator> <symbolic expression>

5.1.2 Examples

l S

l ~ ~ S t S

t t S

J 3 of indexlist( .S)

5.1.3 Semantics

The contents of any variable declared of type 'symbol is a push

down stack. The value of a variable consists of the current contents of

the t o p m o s t ' l ~ v e l of the push down stack. Assignment statements using

symbol variabl.es. on the l e f t replace the current contents of the topmost

: level of ' i t spush down stack. Applying a single push down operation,

to th e name.ofsueh 11 variable pushes down each level of the stack making

the topmost level (level 0) empty and replacing th e contents stored at level

k with the contents stored previously a t level k-l , for k = 1,2, •• . ,

maxlevel,+ l . The empty topmost level may then acquire a value as i t s

contents by means of the execution of an appropriate assignment statement.

A lower level of th e push down stack i s inaccessible to the operation of

extraetiQs eOfttents unt i l the execution of a pop up statement restores it . to

the topmost: level . Applying a single pop up operator, t , to the name of a

varia.ble de.stroys th e contents .o f the topmost level ( level 0) and replaces

Page 43: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 43/53

- 36 -

the contents stored a t level k with the contents stored previously a t

leve 1 k + 1, for k = 0, 1, • . . , maxlevei-I. A push down opera tor (pop up

operator) consisting of n consecutive occurrences of a single push down

operator (pop up operator) has th e same effect as n consecutive applica-

' t ions of a single push down operator (pop up operator). A push down

operator (pop up operator) is applied to a symbolic expression by (1 ) evaluat

ing th e symbolic expression and (2 ) determining i f th e resul t is an atomic

symbol or not. (3 ) I f not, nothing is done. (4) I f so , th e operator is

applied to the push down stack named by th e atomic symbol as described above.

Whatever structure occupies th e contents of a symbol variable, S, may become

the contents of a lower level of, th e push down stack in S by applicat ion of

the push down operator to S. In part icular , l i s t structures may be stored in

the push down stack in S.

5.2 Additional Types of For Statements

5.2.1 Syntax,

<for l i s t eleIl!-ent> : : = • .• I <symbolic expression>

elements of <symbolic expression>

attr ibutes of <symbolic expression>

<for-clause> ::= •.• I!£E <symbolic expression> ~ < f o r l is t> do

paral lel for [<formal parameter l i s t>]

elements of [<symbolic expression l i s t>] do

parallel for [<symbolic expression> ]

elements of [<symbolic expression>] do

5.2.2 Examples

for l i s t elements

S

attr ibutes of S

elements of S

Page 44: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 44/53

- 37 -

for clauses

for S 1, F...f{j, <'1>, l a s t of Tl do

for S <- elements of <I> do

for S <- at t r ibutes of T do

paral le l for [ I , J ,K] <- elements of [ [S], [T], [U] ] do

5.2.3 Semantics

We may wish to generate the elements of a l i s t or the at t r ibutes

of a description l i s t one by one in order to as-sign. them to the control led

variable in a for statement. For this purpose, the for l i s t elements,

at t r ibutes of S, and elements of S, are introduced. Here, at t r ibutes on

the descript ion l i s t of the value of S, which must be an atomic symbol,

are generated in th e order that they occur by at t r ibutes of S, an d elements

of S, generates the successive elements of the l i s t which is the value of

S. In th e foJ:mer ease, S may be any symbolic expression with an atomic

symbol as value. In the l a t te r case, S may be any l i s t valued symbolic

expression.. Successive elements generated are assigned to th e control led

variable given in the for clause.

Paral le l generation i s also permissible. For example: i f

s <- [ A , B ~ C l , T <t - [D,E] and U [F ,G,H,I] have been executed where th e

variables A through I .have as values their respective names, then· executing

the statement

paral le l for [I,.J,K] elements of [ [S] , [T], [U] ] do

L <- [L,I ,J ,K] ;

causes the 'following to happen. Fi rs t , a l l f i r s t elements of the l i s t s

contained in S,T, and U respect ively are generated and placed in the contents

of the control led variables I , J , and K respect ively. Control then passes to

the body of the paral le l for statement and returns when finished with i ts

execution. On th e second cycle, al l . second elements of S,T, and U are

Page 45: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 45/53

- 38 -

generated and placed in th e control led variables I , J , and K respect ively.

Control then passes to the statement following the do and returns. On the

third cycle, a l l third elements are generated, on th e fourth cycle, a l l

fourth elements are generated, and so on. I f any l i s t runs out of elements

before any of i ts neighbors, the symbol n i l keeps gett ing generated as the

n th element of that l i s t whenever'n exceeds the number of elements on the

l i s t . 1he para l le l generation stops on th e f i r s t cycle before the symbol

n il would be generated from a l l l i s t s . The number of control led variables

is arbi trary but must be the same as the number of l i s t s designated in th e

symbolic expression l i s t .

List valued symbolic expressions may be used to supply l i s t s of controlled

variables and l i s t s of l i s t s to generate in paral le l , as, for example, in the

construction

parallel for [V] (- elements of [W] do

where th e statements V (- [I ,J ,K] and W (- [ [S] , [T], [U] ] have been

executed previously. At the end, L should contain [L,A,D,F,B,E,G,C, ni l , H,

, n i l , ni l , I ] .

5.3 Editing Statements and Description List Editing Statements

5.3.1 Syntax

<editing statement> ::= inser t <l i s t expression> <insert ion locator part>

<symbolic expression> I delete <selector part> of <symbolic

expression> I delete <symbolic expression> .1 al te r

<selector part> of <symbolic expression> !£ <expression>

<description l i s t edit ing statement>

<insert ion locator> ::= before <positi9n> of I af ter <position> of

<insert ion locator l ist> ::= <insert ion locator> I<insert ion locator l i s t> , <insert ion locator>

Page 46: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 46/53

- 39 -

<insert ion locator part> ::= <insert ' ion locator> I

«inse r t ion locator l i s t»

<selector l is t> ::= <selector> <selector l i s t> , <selector>

<selector part> : := <selector> «se lec tor l i s t»

<descript ion l i s t edi t ing statement> ::= the <symbolic e x p r e s s i o ~ ~

of <symbolic expression> <is phrase> <expression>

<is phrase.> ::= I is not I is also

5.3.2 Semantics

Editing statements are used to transform, permute, a l te r , and

delete elements of l i s t s . The inse r t construct ion causes a l i s t s t ructure

given by a l i s t expression to be inserted a t the l i s t of places in a given

l i s t specified by an insert ion locator part . The l i s t on which insert ion

i s to be performed is obtained by evaluating the symbolic expression found

as the las t item in th e construct ion. All th e inser t ions take place simul-

taneously. The f i r s t delete construct ion given in the syntax equation for

edit ing statements above performs simultaneous deletions of a l i s t of par ts

within the l i s t obtained by evaluating th e symbolic expression. The l i s t

of parts to be deleted i s specified by the selector par t in accord with the

semantics of selectors . The second delete construct ion deletes the symbolic

expression and i s equivalent to an erase command. The a l te r construct ion is

the same as the f i r s t delete construct ion except i t replaces each item of

the l i s t of par ts deleted with an arbi t rary expression.

5.3.3 Examples

Suppose S (- [X,A,A,X] has been executed. Then the statement:

inse r t Y before l as t of S; changes the value of S to l<Dok l ike [X,A,A,Y,X].

Similarly, the statement: inse r t [ [Y,Z] ] (af ter 1 g of, before las t of) S

ch,angesthevalue of S to look l ike [X, [Y,Z], A,A, [Y,Z], X]. The s ta te-

ment: delete 3 rd before las t of S; al ters th e value of S to look l ike

Page 47: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 47/53

- 40 -

[A,A,X], and delete a l l A of S; causes the value of S to be changed to

[X,X]. In a similar vein, the statement: al ter a l l A of S to [ [C,C] ] ;

changes the value of S to look l ike [X, [C,C], [C,C], X].

5.3.4 Description List Editing Statements

Description l i s t edit ing statements add or delete values on

descript ion l i s t s . They supplement th e role performed by assigrunent s ta te-

ments in th is ·regard. Suppose that S (- / [types: mu,pi, rho] [color: red]

has been executed. Then, i f the statement: the color of S is green ; is

executed, the value of th e at t r ibute ' color ' on the description l i s t of S is

replaced with the new value 'green' . This yields the al tered descript ion

l i s t / [types: mu,pi,rho] [color:green] as a resul t . On the other hand,

the statement: th e color of S is also green ; could be executed. Instead of

replacing th e color ' r ed ' with th e value 'green' , the l a t te r statement appends

the value 'green' to the value l i s t following the at t r ibute 'color ' . This

yields t h ~ description l i s t / [ types:mu,pi ,rho] [color: .red,green] as a

resul t . Final ly, description l i s t edit ing statementsmay.be used to delete

values from value l i s t s of a specific at t r ibute . Executing the statement:

the typeS of S i s not pi; al ters the above description l i s t to be of the form

/ [ types: mu,rho] [color: green].

5.4 Transformed Formulae

5.4.1 Syntax

<transformed formula> ::= <formula expression> <schema variable>

<schema variable> ::= <variable>

<schema assigrunent> . : := <schema variable> (- [<schema>]

<schema> ::= <schema element> I <schema>, < s c h e ~ element>

< s c h e m ~ element> : := <variable> I <single production> I<paral lel production>

Page 48: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 48/53

- 41 -

<single production> ::= <formula pattern structure>l ~ < f o r r n u l a expression>

1<formula pattern structure> • ~ < f o r m u l a expression>

<parallel production> : := [<parallel elementS>]

<parallel elements> : := <variable> I <single production>

<paral lel elements>, <variable> I

<parallel elements>, <single production>

5.4.·2 Examples

Transformed Formula

Single Production

A: form X (B:form + C:form) .A X .B + .A X .C

Schema Assignment

S (- [PI Rl, [P2 R2, P3 R3], P4 R4]

A complete example is given a t th e end of the discussion of th e semantics.

5.4.3 Semantics

This section uses the concepts of description l i s t s and

formula patterns discussed in sections 3.2.5 and 4.1 respectively.

·Let 'F and G be formulae, and le t P be a formula pattern. The application

of the production P to the formula F is defined as follows:

1. I f F==P is false (see section 4.1.2) then the

application is said to fai l .

2. I f F==P is t rue, then the application is saidto succeed, and ,F is transformed into th e

value of the expression replace(G). As

explained in section 4.1.2, i f F==P isand i f P contains extractors, sub-expressions

of F matching corresponding parts of Pa r e

1.For the definition of <formula pattern structure>, see section 4.1.1.

Page 49: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 49/53

- 42 -

assigned as values of th e extractors.Furthermore, i f th e names of the e x t r a c t o ~

'variables are used as atoms in th e construc

t ion 'of G, then executing the procedure

'rep1ace(G) subst i tutes these extracted sub

expressions for occurrences of the names of

th e extractor variables causing as a resul ta rearrangement of th e sub-expressions of Finto the form expressed by the structure of

G.

For example, the distr ibutive law of mUltiplication over addition may,

be executed as transformation by applying the production

A: any X (B: any + C:any) .A X .B + .A X .C (1)

to a given formula. , S u p p , o s ~ F ~ X t 2 X (Y+ sin(Z)) . Then s.pp1ying th e

production (1 ) to F wil l resul t in the extraction of the sub-expressions

Xt2, Y, and sin(Z) into the variables A,B, and C respective1Yt and wil l

cause the replacement of th e atomic names A,B, and C occurring on the r ight

hand side of (1) with these sub-expressions resulting in the transformation

of the vaiue of F into the formula Xl2 X Y + Xt 2 X sin(Z).

A schema is a se t of transformation rules. Each rule is either a

single production or a l i s t of single productions defining a paral le l produc-

tiona Variables occurring in a schema must have single productions as values.

Expressions of the form F S are formula primaries, and thus may be used as

constituents in the ,construction of formulae. The value of such a formula'

primary i s a formula which results from applying the productions of the schema S

to the formula according to one of th e two possible sequencing modes explained

as follows.Sequencing,modes

give the order inwhich

productions of a given

schema, S, are applied to a given formula, F, and to i t s sub-expressions. The

two sequencing modes differ in the order in which a given production wil l be

applied to different sub-expressions of F, and in the conditions defining ,when

to stop.

Page 50: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 50/53

- 43 -

1. One-by-one sequencing

One-by-one sequencing corresponds to a syntactic construction

of the fonn S f- [Pl

,P2

, . . . , Pn] . For j f - l step 1 unti l n,

production P. is applied to F. I f the application of p. succeeds,J J

P. ' s transformation is applied to F and control returns to th e f i r s tJ

production, PI ' Which is reapplied to th e resu l t . I f p. fa i ls toJ

apply to F, i t is applied recursively to each sub-expression of F.

Therefore, production Pk

is applied to F i f and only i f production

Pk

-l

is not applicable e i ther to F i t se l f or to any sub-expression of F.

This sequencing wil l stop either when no production can be applied to F,

or any of i t s sub-expressions, or when a production containing . ~ h a s

been executed.

2. Paral le l sequencing

Paral le l sequencing corresponds to a syntactic construction of

the fonn S f- [ [Pl

,P2

, . . . , Pn]]. Here for j f - l step 1 unti l n

production P. is applied to F. I f the application of P. fa i ls ,J J

production Pj +l is applied to F, and so on up to Pn . I f a l l single

productions of a paral le l production fa i l a t th e topmost level of F,

then the Whole sequence i s applied recursively to the main sub-

expressions of F. Thus, in paral le l sequencing, each one of the

productions is applied a t level k of the formula F only i f a l l produc-

t ions have failed a t level k- l . The termination condition is reached

When a l l productions fa i l a t th e bottom level of F or when a production

containing has been executed.

In general, a schema wil l have a combination of both sequencing modes.

The s c ~ e m a variable, S, has to be declared of type symbol. Optionally,

a description l i s t may be associated with S. I f the special attr ibute index

occurs in the description l i s t of S, then when the transformation has been

completed, the value of an integer variable used as the value of the at t r ibute

Page 51: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 51/53

- 44 -

index is set to 0 i f no transformation took place, i . e . , no production. was

applicable to F. The variable is set to 1 i f a t least one transformation

took place and exi t occurred because no further production of S was

applicable. Finally, the variable is set to 2 i f a production containing

. ~ w a s applicable. The following complete example of a schema clears

fractions in arithmetic expressions.

begin F,X,A,B,C ; symbol S,P, T

A ~ A : a n y ; B ~ B : a n y ; C ~ C : a n y p / [operator: +] [ ~ : ; T / [operator: X] [ ~ : true]

S [A t (-B) 1 / .At. B ,

A Ipl (B/C) (.A X .C + .B) / .C ,

A ITI (B/C) (.A X .B ) I .C ,

A - B/c (.A X .C - .B ) / .C ,

B/c - A (.B - .A X .C) / .C ,

A / (B/C) (.A X .C ) / • B ,

(B/C;) / A .B / (.C/.A) ,

(B/A) t C ~ [ . B t .C / .A t .C]

F (X + 3/X) t 2 / (X - l/X)

PRINT (F , S) end-The above program will print X X (Xt 2+3) t 2/ (Xt 2x (x t 2-1» .

6. Special Functions

The following special functions are available:

Derv(F,X) which takes the derivative of a for.mu1a F with

respect to the fo.rmu1a variable X.

Rep1ace(F) 'defined in section 3.1.4.3.

Empty(L) which is a Boolean procedure having the valuetrue i f the contents of the symbol variable Lis empty, and having the value false otherwise.

Page 52: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 52/53

Mark(F)

Test(F)

Clear(F)

Create (N)

Eradl(S)

Length(L)

Cells

- 45 ..

Which is a function designator whose value isth e value of F but which marks F with a specialbi t . Thus, for the expression Mark(F) + G,the value is 'a + f" where a = VALUE (F) wi th aspecial b it attached, and Where = VALUE(G).

which is a Boolean function deSignator whosevalue is true i f F is marked and false otherwise.

which is a function designator whose value is

VALUE(F) but which has th e special marker b it

cleared.

which is a symbol function designator whose value

is a l i s t of N created variables with names givenby a numeric code.

which erases the description l i s t attached to thesymbol S.

which is an integer· function designator having as

value the number of elements in the topmost levelof the l i s t which is the value of L. This specialfunction is included as a t ightly coded routinefor the sake of efficiency.

which is an integer primary whose value a t any

time is the number of cells remaining on the available space l i s t .

7. History and Implementation

Formula Algol has been under development at Carnegie Inst i tute of

Technology for three years since January 1963, and has undergone cont\nua1

evolution and expansiqn since that date. In August, 1963, an interpret ive

version was running and was reported a t th e Working Conference on Mechanical

Language Structures in Princeton,. N. J. [2J. The present version of Formula

Algol has been implemented as a compiler on the CDC G21 computer [6]. I ts

syntax analyzer is written as a set of Floyd-Evans productions [3],[4], . i t s

code generators are written in the notation of Feldman's Formal Semantic

Language [7], and i ts run-time routines are written in machine code for the

. purpose of constructing, testing, and manipulating formulae and l i s t structures

at run-time. A standard linked l i s t memory scheme has been used.

Page 53: Perlis a Definition of Formula Algol Mar66

8/3/2019 Perlis a Definition of Formula Algol Mar66

http://slidepdf.com/reader/full/perlis-a-definition-of-formula-algol-mar66 53/53

REFERENCES

[ 1] Naur, P. • !! . , Revised Report on the Algorithmic Language

ALGOL 60, Communications of the ACM, Vol. 6,

pp. 1-17, (January 1963).

[2] Perl is , A. J. and l turriaga, R., An Extension to ALGOL for

Manipulating Formulae, Communications of the ACM,

Vol. 7, p. 127, (February 1964).

[3]· Floyd, R. W., A Descriptive Language for Symbol Manipulation,

Journal ACM, Vol. 8, p. 579, (1961).

[4] Evans, A., An ALGOL 60 Compiler, Annual Review in Automatic

. Programming, Vol. 4, Pergammon Press.

[5] Yngve, V. H., COMlT Programmers Reference Manual, The M.l.T. Press,

(September 1961).

[6] l turr iaga, R., Standish, T. A., Krutar, R. A., and Earley, J. C.,

Techniques and Advantages of Using the Formal

Compiler WritingS y s t ~ m FSL

to Implement a Formula

Algol Compiler, to appear in Proceedings .Spring Joint

Computer Conference 1966, Spartan Books.

[7] Feldman, J . A., A Formal Semantics for Computer Languages, Doctoral

Dissertation, Carnegie Inst i tute of Technology, (1964).

[8] Feldman, J .A . , A Formal Semantics for Computer Languages and i ts

Application in ' a Compiler-Compiler, Communications of

the ACM, Vol. 9, p. 3, (January 1966).