Contact us Heritage collections Image license terms
HOME ACL Associates Technology Literature Applications Society Software revisited
Further reading □ Overview1962: An outline of Fortran1962: Operating experience with Fortran1962: Implementation of Fortran on Atlas1962: Proposed target language (BAS)1962: BAS binary card1963: Intermediate Atlas symbolic programming language (INTERASP)1963: Addendum1963: A primer for Fortran programming1964: Atlas Fortran manual: Part I1964: Part II1964: Using HARTRAN1965: System note 41966: Fortran on Atlas □ Atlas 2 at AWRE □ 1965: BAS subroutines1965: System notes1966: S3 Fortran □ Titan □ 1966: System note 11966: System note 21966: Fortran on Titan1966: Compile Master on Titan1966: System Note 31966: Differences between S3 dialect and Fortran II1966: Magnetic tape library subroutines1967: T3 Fortran reference manual
ACD C&A INF CCD CISD Archives Contact us Heritage archives Image license terms

Search

   
ACLApplicationsHartran :: Hartran and Fortran on Atlas
ACLApplicationsHartran :: Hartran and Fortran on Atlas
ACL ACD C&A INF CCD CISD Archives
Further reading

Overview1962: An outline of Fortran1962: Operating experience with Fortran1962: Implementation of Fortran on Atlas1962: Proposed target language (BAS)1962: BAS binary card1963: Intermediate Atlas symbolic programming language (INTERASP)1963: Addendum1963: A primer for Fortran programming1964: Atlas Fortran manual: Part I1964: Part II1964: Using HARTRAN1965: System note 41966: Fortran on Atlas
Atlas 2 at AWRE
1965: BAS subroutines1965: System notes1966: S3 Fortran
Titan
1966: System note 11966: System note 21966: Fortran on Titan1966: Compile Master on Titan1966: System Note 31966: Differences between S3 dialect and Fortran II1966: Magnetic tape library subroutines1967: T3 Fortran reference manual

Implementation of FORTRAN on Atlas

I C Pyle

July 1962

Atomic Energy Research Establishment, Harwell, England

Proceedings of a Symposium held at the London School of Economics, Editor Peter Wegner

1. Introduction

The general approach adopted in designing the Atlas Fortran compiler is one of machine independence, rather than language independence. The compiler is tied closely to the FORTRAN source language, but only loosely to the Atlas computer. This means that the compiler could work with very trivial changes on virtually any computer which has a Fortran system, and it could be fairly easily modified to produce target programs for any computer. Of course, it is quite a large program, and would need a reasonably large computer to work efficiently. One of the points which should be mentioned initially is that there is no sophisticated treatment of two level storage problems; it is presumed that the relevant computers have large enough stores for this not to be serious.

Since a Fortran compiler treats routines, not whole programs, we do not think it is necessary to be able to process large pieces of program. Various tables of finite size are used during compilation; if one gets filled, the compiler will give up and tell the source of programmer to break up the routine into smaller sections. We intend to keep all the tables in the main store of Atlas, so there will be no time lost because of transfers to and from tape.

2. Writing in FORTRAN

A compiler is, after all, just a large and rather complicated program, which can be written in any convenient language. We chose to write in FORTRAN for a variety of reasons, some subjective (we like it), but most objective.

The first point is that the compiler can then be run on any computer which understands FORTRAN. This is particularly important for a compiler for a new computer, since it can be thoroughly tested before the new computer arrives, without having to resort to simulation. We expect that our compiler will be checked out well before the N.I.R.N.S. Atlas is ready.

The other reason is not peculiar to our compiler, but is simply related to its size. Any program as large as this would get out of hand without a firm, but flexible framework. FORTRAN source language is far preferable to a symbolic machine language, and the Fortran Monitor System provides the programming system within which we can work.

Routines are written and compiled independently, then combined on loading to form the program. This arrangement makes it easy for us to change routines in the compiler during testing and, after we have got it working, to improve either facilities provided or efficiency of operation. It also makes it very easy to produce different versions of the compiler for different computers, in association with the Atlas Fortran project, routines are being written to compile for the Orion.

The only disadvantage which arises through writing in FORTRAN is that tables of small integers can be stored only one number per word, because packing and unpacking are awkward. The consequent limitation on available storage is accepted.

3. Programming System

In preparing a FORTRAN system for a new computer, it is not sufficient to provide a compiler alone, there has to be a library of routines which can be used by compiled routines. These will control input/output, and evaluate mathematical functions. In addition, there has to be at least a loader, to combine routines and initiate execution, but preferably a programming system which will control the processing of the various routines of a job.

The design of the programming system, especially the intermediate language used for communicating routines to the loader, is important, and influences the compiler and the source language, because of the facilities which can be provided.

The programming system to be used on the N.I.R.N.S. Atlas is called Hartran; it will provide facilities familiar to users of the Fortran Monitor System. The intermediate language used in the Hartran system is called BAS (Binary and Arbitrarily Symbolic). The information is principally in relocatable binary, but there is sufficient symbolic content to allow very flexible communication between independently compiled routines. A full description is given elsewhere (Curtis and Pyle, 1962). It is slightly more flexible than the BSS language used in IBM Fortran (IBM, 1958), the differences mainly being connected with storage of arrays.

The target language of the compiler is BAS; routines are output in this form, so that they can be loaded on several occasions without re-compilation. The use of BAS as target language allows us to generalize the FORTRAN source language slightly (PARAMETER and PUBLIC, described later).

4. Two Level Storage Problems

Most computers (and Atlas is no exception) have several types of internal store, of different sizes and accessibilities. In general, the most accessible stores are the smallest. Consequently, information has to be moved from one type of store to another at various stages of a calculation. The two-level storage problem is to determine the best times for these transfers. We do not know of any general solution of this problem.

Two level storage problems arise in two distinct contexts on Atlas, but fortunately the hardware of the machine renders them relatively unimportant and a simple treatment is acceptable.

(i) There are a number (eighty) of special registers called B-registers, which can be used to modify the addresses of instructions. These are used to reference locations which vary during execution (array elements, or dummy variables; ordinary variables are relocated on loading, and not changed during execution). The problem is, what happens if more than eighty such variable locations are needed?

Our solution is to treat the B-registers as private to each routine, and assign one for each variable location in the routine. We can insist that the total used in the routine is less than eighty. We have never seen a routine which needs more than twenty; anyway, a large routine can always be broken down. Thus there is no limit to the total number used in a program.

In order that a routine should not disturb the B-registers of the routine which activates it, it must store the contents of all the B-registers it needs before changing them, and put them back before returning. (If there is no return, then they need not be saved.) This transfer on entry to and exit from subroutines introduces an inefficiency of a few per cent, which is accepted.

(ii) The main store of Atlas (core and drums) is large; of order 100 K. Thus few programs will need to use magnetic tape as a backing store. For those which do, instructions are provided for the programmer to use, to control transfers to and from tape.

In the basic system there are instructions for manipulating tapes (searching and transferring blocks of information). The Hartran system allows the programmer to specify how his large program is to be divided into chapters, and how variables are to be arranged in blocks. Library routines are provided to transmit chapters and blocks, but the programmer has to decide when to use them.

5. Transfer to Atlas

At first sight there seems to be a snag in the method described, because until the compiler is there, the Atlas cannot understand FORTRAN. How then are we to get the compiler in?

The solution is based on the fact that the compiler is written in its own language, so we can use a bootstrapping technique, starting with another computer for which a Fortran compiler already exists: e.g. the IBM 7090. We run the Atlas Fortran compiler on this computer (as for testing) and feed it with a copy of itself (see Fig. 1). The output is a translated version of the compiler, which can then be loaded into Atlas. The compiler then operates under the Hartran programming system, just like any other FORTRAN program.

1. 7090 FORTRAN → BSS 2. 7090 BSS → 7090 3. FORTRAN FORTRAN → BAS 4. BSS FORTRAN → BAS 5. 7090 FORTRAN → BAS 8. ATLAS BAS → ATLAS 6. FORTRAN FORTRAN → BAS 7. BAS FORTRAN → BAS 9. ATLAS FORTRAN → BAS 12. ATLAS BAS → ATLAS 10. FORTRAN JOB 11. BAS JOB 13. ATLAS JOB
Fig 1

In this diagram, a box represents a program. At the top is the name of the language it is expressed in, which may be an external language or the machine language of a computer executing it. At the bottom is a description of the program; for translation programs we specify the input and output languages. A loader is like a translation program, except that the output language is the appropriate machine language.

Boxes 1 and 2 represent programs which already exist: the Fortran compiler and loader for the 7090. BSS is the name of the intermediate language used in the IBM Fortran. Box 3 represents the Atlas Fortran compiler, which we are writing. It translates from FORTRAN into the BAS intermediate language. Boxes 4 and 5 represent programs which are produced automatically, giving a version of the Atlas Fortran compiler which runs on the 7090. Box 6 is a copy of box 3, which is input to the new compiler. Box 7 represents the program which is output, from the 7090, in a form ready for transfer to Atlas.

At this stage, we need an Atlas, and a loader, which has to be written and input independently using some primitive method. Box 8 represents the BAS loader for Atlas. Box 9 represents the ultimate form of the compiler, in Atlas. A job whose program is written in FORTRAN (box 10) may then be input, and converted to BAS (box 11). Box 12 is the same as box 8, the BAS loader, which combines the routines of the job and initiates execution (box 13).

6. Machine Dependence

It will be clear from the above discussion that we rely on the fact that it is not necessary for a compiler to run on the machine for which it produces output: compilation and execution need not be carried out on the same machine. We refer to the compiling machine and the target machine: initially we use the IBM 7090 and the Atlas; eventually both will be Atlas.

We classify routines according to their machine dependence: they are either machine independent, or target machine dependent, or compiling machine dependent. The machine independent part of the compiler is concerned with analysing the source routine and carrying out general optimization. This is described in more detail below.

Target machine dependent routines are concerned with the synthesis of instructions in target language. Since the repertoire of instructions is machine dependent we do not try to produce output in a machine independent form. Instead, we send control to an appropriate routine. Thus the names of routines can be thought of as an UNCOL (Universal Computer Oriented Language). For example, when an unconditional transfer is required, we enter a subroutine called JUMP. The Atlas version of this subroutine compiles a TRA instruction; the Orion version compiles a two-address 75 instruction. The instruction repertoire may also lead us to do some special optimization which is target machine dependent.

For example, on Atlas, subtraction may be slower than addition, even if the accumulator is first to be negated (but not if it is to be cleared). We therefore permute the elements of the expression, subject to the algebraic rules of associativity and commutativity, to arrange that subtract (SU) operations are avoided if possible, and replaced by clear and subtract (CS) or negate and add (NA).

Thus

      A = B + C- D * E 

is compiled as

PCS D
FMP E
FAD B
FAD C
STO A

i.e. (-D) * E + B + C → A 
and
      I = J + K - L - M
is compiled as

XCA L 
XAD M 
XNA J 
XAD K 
STO I 

i.e. -(L + M) + J + K → I

Compiling machine dependent routines are concerned with the compiler's own input and output. Initialization of the various tables is also compiling machine dependent.

The compiler consists of several sections which must be brought into the working store as they are needed. These correspond to chain links in the Fortran Monitor System, or to chapters in Mercury Autocode. The organization of chapters depends on the compiling machine, so this is another compiling machine dependent feature.

When the compiler is first written compiling for Atlas on the 7090, we need the machine independent routines, and target dependent routines for Atlas, but compiling machine dependent routines for the 7090. Later, we must prepare compiling dependent routines for the Atlas, and use these when we transfer the compiler to Atlas.

7. Extensions to FORTRAN Source Language

At the beginning of the Atlas Fortran project, it was decided that the FORTRAN II source language used on the IBM 704,709,7090 is somewhat restrictive, and that because of the ease of modification of FORTRAN programs, a small number of changes would be acceptable if (i) any features removed are replaced by better ones, (ii) most routines would need no change at all, and, (iii) where changes are needed, the places are easy to find.

Similar changes are being proposed by IBM for FORTRAN IV, and there is a close similarity between the dialects.

As an example of a proposed change, logical expressions can be written using the operations .NOT., .AND., .OR., .GT. (>), .GE. (≥), .EQ. (=), .NE. (≠), .LE. (≤), .LT. (<) and variables of mode LOGICAL. An IF statement can test a logical expression or a logical variable.

The following extensions are only in Atlas Fortran.

(i) The values of several variables can be changed in one statement, e.g.

      X, Y, Z = EXPR

(ii) An expression may contain elements of mixed modes REAL and INTEGER, e.g.

      2 * X

(iii) A subscript may be an expression, e.g.

      A(I + J, K(L) )

(iv) We wish to remove some of the restrictions in the DO statement, e.g. that the increment must be positive, and the body is always executed at least once. Instead of altering the meaning of the DO statement, and introducing incompatibilities, we thought it better to introduce a new statement with different semantics. The principal difference between the new FOR statement and the DO statement is that the body will not be executed if the parameters are the wrong way round, e.g.

      FOR I = 10, 1, 1

Further extensions could probably be also allowed for DO statements, without incompatibility: e.g. allowing expressions in the parameter positions, and taking account of the sign of the index. A REPEAT statement can be used instead of a numbered statement to end the loop.

The above changes are all notational: the same effect can be obtained in FORTRAN II by breaking up the statements into a number of simpler steps.

A more powerful change is concerned with communication between routines by hidden parameters. The declaration

      PUBLIC A

specifies that the name A in this routine represents the same thing as the name A in any other routine which specifies it to be PUBLIC. (In the absence of any declaration, the name is private; a COMMON declaration sets up correspondence by position in the common list, rather than by name). The implementation of PUBLIC is a feature of the BAS loader; the compiler has only to record symbolic information in the target routine.

Another change associated with the BAS loader concerns storage assignment for arrays. This can now be parametric, and fixed at load time rather than compile time. For example,

      PARAMETER I, J 

allows us to have

      DIMENSION X (I, J) 
      PUBLIC Y (I, J)

where these are actual arrays (not dummies; FORTRAN IV allows adjustable dimensions for dummy arrays, but otherwise insists on constants).

No storage is assigned on compilation, but on loading we can have a directive such as

* DEFINE I = 20, J = 50

before the routine, and appropriate storage will be assigned.

8. Optimization

The level of optimization at which we aim is only slightly higher than that in IBM FORTRAN. We do the same elimination of common subexpressions, so that repetitions in an expression will be evaluated once only. The subscript analysis is rather more complicated as the allowed form for subscript has been generalized. References to members of an array are written as the array name followed by a list of subscripts in parentheses. Each subscript may be an expression (i.e. similar in form to a function argument). A single working subscript is derived by combining the expressions in a storage mapping function which depends on the dimensions of the array. Then the array is interpreted as a vector, the working subscript giving the position of the desired element.

The simple minded approach, used in compilers which do not optimize, is to evaluate the storage mapping function each time a reference is made. This is satisfactory if the subscript forms are very simple (of the form I + 2) but becomes time-consuming if multi-dimensional arrays and full expressions in subscripts are allowed.

Optimization of subscripts is based on the assumption that there are (statistically) more references to each array element than there are definitions of the dependent variables. Consequently, we aim to calculate the subscripts at points of definition, rather than on use.

Since it would not be feasible to recognize points of definition of functions or arrays, we classify subscripts as they are met according to their form. Slow subscripts contain array elements or functions. These are not optimized: they are evaluated on use. Fast subscripts contain no element more complicated than an integer scalar. These are optimized: evaluated on definition.

The definition of a subscript might be by an explicit change of value of a dependent variable, or by a controlling loop. During the scan of the source routine all value changes of integer scalars are noted, and a push-down list of current loops is maintained.

Fast subscripts which occur in a loop might or might not depend linearly on the index of the loop. Those which do are initialized before the loop begins, and incremented for each repetition. If they depend non-linearly on the index, they are evaluated at the beginning of every cycle.

9. Outline of the Compiler

The compiler is divided into a number of sections which are executed in sequence for each source routine. The first five sections produce instructions in a symbolic machine language (like ASP) and the final section converts the routine into BAS. After describing the major sections in outline, we will give more detail about some of the processing carried out.

Section 1 reads in the routine one line at a time, and analyses each source statement. During the scan information is recorded in tables for later use. These concern the modes of identifiers, values of constants, fast subscripts, loops, flow of control, and storage assignment.

Before processing each line of the source routine, a printed copy is output for the programmer. If any error is discovered, an extra line is output, giving information about the error: usually it will come under the line containing the error.

This section is completed on reading the END card in the source routine. No further cards are read: all the information needed subsequently is obtained from the tables.

Section 2 deals with expressions which were analysed in Section 1. Symbolic machine instructions are produced and there is a considerable amount of local optimization (i.e. within each statement). Addition and multiplication and the logical operations or and and are assumed to be commutative, and the compiler permutes variables in order to improve the efficiency of the target program. Subscripts are stripped, and either evaluated with the statement or recorded as fast for evaluation on definition. Common subexpressions in a statement are recognized to avoid recalculation.

Section 3 deals with loops in the routine, arising from DO and FOR statements. Instructions are compiled to initialize and increment linearly dependent subscripts.

The processing of this section is carried out sequentially for each loop in the routine, in backwards order of the DO or FOR statements. This means that innermost loops are always treated first.

Each (fast) subscript which is used in the body of the loop is classified as linear or non-linear in the loop index. It is treated here only if it is linear. The subscript will be evaluated incrementally, and the initial value and increment must be set before the loop begins. The initial value and increment are then regarded as subscripts, and will be similarly treated in the next outer loop, if any.

Section 4 analyses the flow of control through the routine resulting from IF and GO TO statements. The object of this is to discover the points of definition of those subscripts which are not controlled by a loop. These result from changes to the values of dependent variables. Instructions are compiled to evaluate the subscripts at the appropriate points.

These three sections produce symbolic instructions in separate streams, with internal reference numbers attached to indicate their desired positions in the target routine.

Section 5 merges the outputs of the earlier sections, using the internal reference numbers as keys.

During the merge, each instruction address is compared with the list of dummy arguments (formal parameters) of the routine, in order to know what adjustments will be necessary during execution. This produces the body of the target routine, after which the prologue and epilogue are compiled, for linking this routine with its caller, and then the tables of constants used by the routine, and storage for its own variables.

The relative locations of all parts of the routine are determined in this section (as in the first pass of an assembly program) and Section 6 produces the BAS routine by making the appropriate substitutions.

A storage map is printed, giving a list of identifiers used, with their modes, types, and locations assigned, together with other information which might be useful to the programmer. If any errors were detected, explanatory messages will be printed. This arrangement allows comments to be made about possible errors, without suspending compilation.

10. Input of Statements

Compiling machine dependent routines are used to read in a line (PUN) and output a copy of it (PIOU). These are used by machine independent routines PICD, which checks whether the line is a comment or blank, PINC, which sets up a continuation if there is one, and CIBS, which sets up the first line of each statement. The structure of the input section is shown in Fig. 2.

PINC: Enter PICD Contin Set up line image, with end of line flag PIOU /> Preserve line image Set up end of statement flag /> Reset ITH Return PICD: Enter PIIN Comment Blank PIOU Return CIBS: Enter Retrieve line image and set up with end of line flag PIOU /> Reset ITH Return
Fig 2

Whenever a scan reaches the end of line flag, routine PINC is activated to find a continuation. If there is none, an end of statement flag is set up to trigger off final processing of the statement.

There can be any number of continuation lines for each statement. This means that the first line of each statement is always read in before the previous statement is finished. Routine CIBS retrieves this line and sets it up at the beginning of each statement.

The only exception is the END statement, which defines the physical end of the routine. We do not allow this to have any continuations, and will never read beyond the end of line flag.

11. Scanning Procedure

As an example of the scanning technique used, we give the routine for collecting an unsigned decimal integer. This is used in processing DIMENSION statements, and for the successor statement numbers in IF and GO TO. It is written as a function, whose value is that of the integer read (see Fig. 3).

      FUNCTION INTEG(J1)
C     THIS ROUTINE COLLECTS AN UNSIGNED DECIMAL INTEGER
      COMMON ITH, IST
C     THE STANDARD COMMON IS NOT GIVEN IN FULL
      DIMENSION IST(72)
      J = IST(ITH) - 16
 1    ITH = ITH + 1
      I = IST(ITH)
      GO TO (1,4,4,4,4,2,4,4,4,4,2,4,4,4,4,
C     1 IS SPACE, 6 IS EOL, 11 IS $ OR PI, REMAINDER ARE PUNCTUATION.
     1     3,3,3,3,3,3,3,3,3,3,4,4,4,4,4,4,
C     16 TO "% ARE DECIMAL DIGITS, REMAINDER ARE PUNCTUATION.
     2     4,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,
C     32 IS PUNCTUATION, REMAINDER ARE LETTERS.
     3     5,5,5,5,5,5,5,5,5,5,5,5,5,5,4,1),I
C     62 IS ERROR, 63 IS ERASE, REMAINDER ARE LETTERS
 3    J = J * 10 + I - 16
      GO TO 1
 2    CALL PING
      GO TO 1
 5    CONTINUE
 4    ITH = ITH - 1
      INTEG = J
      RETURN
      END
Fig 3

The scanning is carried out using a pointer ITH and an array IST, in common. The array represents the contents of the current card, successive elements being integers which represent the characters on the card. The code used is based on the Atlas internal code, using integers in the range 1 to 63. A particular number (6) is put after the last card character, indicating the end of the card. Similarly code number 7 is used to indicate the end of the statement. The integers 16 to 25 represent the decimal digits 0 to 9.

The routine is entered with ITH pointing at a digit, and the scan is to accumulate the integer which it introduces. Spaces (code 1) and erases (code 63) are to be ignored, end of line flag (code 6) and π or $ (code 11) to bring in a new line. The different types of character are distinguished quickly by means of the 63-way computed GO TO, controlled by the current character. In this computed GO TO, statement number 1 advances the scan (ignoring the current character;), 2 brings in a continuation, 3 accumulates the integer, and 4 and 5 terminate the scan (4 is for punctuation, 5 for letter, but since both act in the same way we could have used the same number for both). At the end, ITH has to be stepped back one character, because the end of the scan is only recognized when it has gone one character too far.

12. Classification

The type of each statement is determined by a preliminary scan of its first line. This scan stops on reaching the end of the line (or a Hollerith constant), and does not bring in continuations. Consequently, we require the source statement to have sufficient information on its first line.

The preliminary scan distinguishes three statement classes, by looking for parentheses (to determine the level), commas, and the equals sign. Arithmetic statements are identified by an equals sign and no subsequent comma at level zero (i.e. not enclosed in parentheses). Loop statements (DO and FOR) are identified by an equals sign and at least one subsequent comma at level zero. Other statements have no equals sign at level zero.

Statements in the last two classes are distinguished by comparing the beginning of the line with a dictionary of key words (e.g. IF, CALL, GO TO, READ). Some types are further classified by comparison with a subsidiary dictionary (e.g. for READ we may have INPUT TAPE, INPUT, TAPE, DRUM). The dictionary search routine stops the scan if the source character . is met. This allows abbreviations, e.g. "DIM." for "DIMENSION".

The reason why a preliminary scan is needed is that the key words are not reserved identifiers: variables can be called IF, GO TO, DO5I etc., and occur at the beginning of an arithmetic statement. There is an important difference between

      DO5I = 1,3
and
      DO5I = 1.3

(although the second is probably a mistake, it is quite legal, and we do not attempt to catch it!)

13. Expressions

Arithmetic statements, DO, FOR, IF and CALL statements may involve expressions, which are analysed by a standard group of routines. At present we use a method similar to the IBM method, described by Sheridan (1959), but as a direct consequence of this symposium we might well use Dijkstra's stack method (Dijkstra, 1961).

The difference concerns the treatment of parentheses. The problem is that the natural algebraic order is not the right order for computing. Different techniques are used to get the right order.

In Sheridan's method, instructions are compiled in the algebraic order, but tagged with numbers representing the computing order. At the end of the expression, the instructions have to be sorted.

In Dijkstra's method, the algebraic order is converted into computing order (reversed Polish) by the use of a stack to hold incomplete subexpressions. Instructions are compiled in the correct order as soon as a subexpression is completed.

The difference would not be serious if all expressions were fully bracketed. However, we must also build in the standard algebraic rules of precedence, by which

      X + Y*Z
is taken to mean
      X + (Y*Z)  
and not
      (X+Y) * Z

Sheridan treats this by putting extra parentheses around every operator, according to its priority (1 for **, 2 for *, 3 for +). Thus the above expression is treated as

      (((( X ))) + ((( Y )) * (( Z )()))

This process produces a high proportion of redundant subexpressions, which have to be removed.

A further disadvantage is that every subexpression must be enclosed by a number of parentheses, equal to the maximum possible priority. We must keep this maximum priority low (4) to avoid an excessive number of redundant subexpressions.

Dijkstra compares the priority of the current operator with that at the top of the stack before adding to it. This avoids producing redundant subexpressions, and also removes the need for restricting priorities, allowing us to use more levels in the hierarchy.

14. Conclusion

We do not intend to implement the whole of the system described in the first instance. In order to get a working compiler more quickly, we will produce a simplified preliminary version, which will have none of the subscript optimization.

This will be done by changing the criterion for recognizing fast subscripts. All subscripts will be treated as slow, and consequently evaluated with the statements in which they are used, rather than on definition. The processing of Sections 3 and 4 is then unnecessary, only rudimentary versions will be put in. By this means, and by accepting some further limitations on the complexity of a source routine to be treated, we will produce a compiler which can process itself, giving a form ready to go to the Atlas.

Once an Atlas compiler produced in this way is working, the immediate aim of the present work will be achieved and the missing sections can be grafted in as they become available, to improve the efficiency of the target routines. The compiler could then be put through itself again.

REFERENCES

1. A. R. CURTIS and I. C. PYLE (1962). A proposed Target Language for Compilers on Atlas. Computer J. 5, 100.

2. E. W. DIJKSTRA (1961). Making a Translator for Algol 60. APIC Bull. No. 7, and Algol-60 Translation, Algol Bull. Suppl. No. 10.

3. IBM (1958). Reference Manual Fortran II, Form C28-6000-1.

4. P. SHERIDAN (1959). The Arithmetic Translator-Compiler of the IBM Fortran Automatic Coding System. Comm. A.C.M. 2, No. 2.

⇑ Top of page
© Chilton Computing and UKRI Science and Technology Facilities Council webmaster@chilton-computing.org.uk
Our thanks to UKRI Science and Technology Facilities Council for hosting this site