2. The compiler

This section gives a brief description of the RTF/68K syntax. Mainly the deviations (extensions and omissions) from standard Fortran-77 are reported here. As a reference we take the VAX-11 Fortran which is available on VAX systems and is an extension to standard Fortran-77 insofar as it supports DO-ENDDO, DO WHILE, IMPLICIT NONE etc. as well as compatibility with old Fortran (Hollerith, hexadecimal and octal constants). The reason is that VAX computers will very often act as hosts for, or will be used in close collaboration with, 68K microprocessor systems.

2.1 Source format

The RTF/68K source code is essentially free-format. Some formatting is required, however, in order to be compatible with the Fortran conventions. The following are extensions to the standard:
  1. Source lines may start in any column except column six (conflict with marker for continuation lines). They should also not start in column one (possible confusion with comment line marker).
  2. Continuation lines are marked in column six with a non-blank and non-zero character as usual. However, this mark may also be omitted (continuation is always obvious from context).
  3. Comment lines are marked by a "*" or "C" or "c" in column 1. "D" and "d" also denote comment lines unless the DEBUG=ON option is selected; then they are proper code lines.
  4. More than one statement may be given per source line. They must be separated by blank(s), or optionally by ";" for better readability.
  5. End-of-line comments may be given. They must be preceded by "!".
  6. Source lines may be up to 132 characters long. Thus, source line numbering in columns 73-80 is not available unless the compilation option LENGTH=72 is chosen.
  7. Lowercase letters are accepted and shifted to uppercase before interpretation unless they occur within strings.
  8. Variable names may contain the special characters underline "_" and '$'. Thus, e.g. Start_Time and SYS$SYSTEM are legal names. For determining the implied data type, the first alphabetic character is taken.
  9. Names may have any length. All characters are relevant to the compiler. For names belonging to external objects (COMMON blocks, subroutines, functions), length restrictions might arise from the subsequent assembler and linker steps.
  10. Lines beginning with a "+" in column one are transferred to the output without changes (just stripping off the "+"), thus allowing for embedded assembly statements.
    Note: A sequence of embedded assembler statements MUST be preceded by a dummy Fortran statement, preferrably CONTINUE, otherwise the embedded code may be inserted at a wrong place.
The following remarks also refer to the source format, but deal with deviations from the standard, rather than extensions.
  1. Blanks are meaningful in RTF/68K. For example, DO100 will not be recognized correctly because a blank is required between keyword and label. GO TO and GOTO, END DO and ENDDO, etc. are however explicitly considered.
  2. The first TAB character met in a source line, if it is within the first eight columns, steps to column 10. Later TABs are converted to blank.
The purpose of handling blanks in the described way is to eliminate some of the huge redundancy of the Fortran language; namely, the kind of redundancy which gives a very wrong semantic meaning to statements with small misprints which are yet formally correct. Maybe you know the example of the Mariner mission which failed due to the Fortran statement

DO 10 I=1.3

where of course a loop was the programmer's intention. But "DO 10 I" is a valid variable name in the standard and was interpreted in that way (because of the "."). - It is invalid and would have been flagged as an error in RTF/68K.

2.2 Constants

According to the data types discussed in the next chapter, there are four types of constants:
Integer, Floating Point, Boolean, and Character String.
Constants may be placed directly in the code, or they can be accessed by names assigned to them with PARAMETER statements (see 2.4.2). Not much needs to be said about the latter three types of constants; examples are:
Floating Point (single precision):
    123.456
    0.00000123456E8
    123456e-3
Floating Point (double precision):
    123456D+2
    1d0
Boolean:
    .TRUE.
    .true.
    .FALSE.
    .False.
Character String:
    'this is the same thing'
    22Hthis is the same thing                  ..but not recommended
    'THIS IS not THE SAME THING'
Integer constants may be decimal, bit-pattern, or ASCII oriented:
    1              decimal; value fits into:   one byte
    -128
    256
    -330                                       (two bytes)
    -32768
    65535
    2000000000                                 (four bytes)
    'FFFF'X        hexadecimal                 (two bytes)
    '1000'X
    'ABCDEF'X                                  (four bytes)
    '377777'O      octal                       (four bytes)
    '111'O                                     (two bytes)
    '101010'B      binary                      (one byte)
    '1000110001'B                              (two bytes)
    'ADAM'A        right justfied ASCII        (four bytes)
    '0'A                                       (one byte)
Integer constants in a context where Floating Point is required are converted at compile-time. Use of integer constants requiring more bytes than are available in the context is flagged as an error; e.g. I1=1000 where I1 is an INTEGER*1 variable. Note that the types
Arithmetic (i.e. Integer or Floating Point)
Boolean
Character string
must not be intermixed, as opposed to VAX Fortran where Integer and Boolean may be mixed. RTF/68K would flag this as an error.

Integer, floating point, and Boolean constants used as subroutine arguments are passed as 4-byte entities, unless word-size modifier intrinsic functions or the option INTSIZE=2 are used (see 2.5.6 and 2.10).

2.3 Data types

The following data types are available in RTF/68K.
  1. Integer data types:

    INTEGER denotes 4-byte signed integer values by default or 2-byte signed integer values with option INTSIZE=2
    INTEGER*1 denotes 1-byte signed integer values
    INTEGER*2 denotes 2-byte signed integer values
    INTEGER*4 denotes 4-byte signed integer values
    DOUBLE INTEGERdenotes 4-byte signed integer values
    BYTE denotes 1-byte signed integer values

Note that the integer data types denote always signed values. In operations with operands of different length (e.g. addition of a INTEGER*4 value and an INTEGER*2 value), the shorter lenghts are sign-extended to the longest length occuring. This may cause undesired effects in non-arithmetic operations sensitive to bit patterns (e.g. IOR, IAND etc.).
  1. Floating point data types:

    REALdenotes 4-byte IEEE floating point values
    REAL*4 denotes 4-byte IEEE floating point values
    REAL*8 denotes 8-byte IEEE floating point values
    DOUBLE PRECISIONdenotes 8-byte IEEE floating point values
    DOUBLE REAL denotes 8-byte IEEE floating point values

Note that the 8-byte values are supported only for systems with the Motorola floating point hardware (co-processors 68881/68882 or 68040 processor including floating point). The approximate decimal precisions and exponent ranges are 1.0e-7, +/-38 for 4-byte and 1.6e-16, +/-307 for 8-byte values. The chip-internal extended precision provides 1.0e-19, +/-4931 respectively.
  1. Floating point data types:

    LOGICALdenotes 4-byte boolean values by default or 2-byte boolean values with option INTSIZE=2
    LOGICAL*1 denotes 1-byte boolean values
    LOGICAL*2 denotes 2-byte boolean values
    LOGICAL*4 denotes 2-byte boolean values

Boolean data are determined in any case by one byte only; the most significant byte in memory or the least significant byte in registers, respectively. An all-zero byte means .FALSE., any other value, preferrably all ones, means .TRUE. This is in accordance with the "set according to condition" instructions of the 68K family.
  1. Character string data types:

    CHARACTERdenotes 1-byte ASCII character values
    CHARACTER*n denotes n-byte ASCII character values
    CHARACTER*(*) denotes m-byte ASCII character values where m is determined by the calling routine for formal arguments; else m=256 by default.

Character variables are represented in memory just as the ASCII characters, without any additional information. Thus EQUIVALENCE of character and other variables is possible. Whenever a character variable is accessed, however, a descriptor containing the necessary extra information is formed. Note that character constants, other than variables, are represented as null-terminated strings.

2.4 Declarations

Declarations are the field where most of the deviations - extensions and omissions - between RTF/68K and the standard show up. The reason is that on one hand, the aim was to introduce the extensions as far as possible by means of declarations, rather than by modifications in the executable statements. This is a rather obvious method and offers a way to enhance existing programs mainly by adding declarations.

On the other hand, the most irregular structures of Fortran are found among the declarations. Some of these structures, e.g. recursion of EQUIVALENCE statements, have been omitted because of their irregularity. Other omissions (lack of some data types) are intended to keep the entire RTF/68K system small, with the on-line applications in mind.

2.4.1 Global and local declarations

A nice way to repeat a common set of declarations (e.g. COMMONs) in many subroutines is with INCLUDE files. Apart from the fact that this is not standard Fortran, the widely used implementations support it. RTF/68K also does.

The other way to introduce globally valid declarations is normally offered by block-structured languages like Pascal etc. Fortran knows one level of declarations: the subroutine level. Subroutines have no block level above them (apart from the semantic binding of COMMONs which is recognized only during linking time) nor below them (apart from statement functions). The advantage is that subroutines can be compiled separately. Disadvantages are that conflicting declarations cannot be recognized by the compiler, and that identical declarations have to be repeated in different subroutines as mentioned above. Block structured languages allow for several, nested block levels. The scope of validity of a declaration is the block where the declaration is made and all lower-level blocks contained in it. If a variable already declared is re-declared on a lower block level, the latter declaration is valid within the lower block.

RTF/68K ranges between Fortran and block-structured languages:

  1. It accepts usual Fortran. The declarations made within subroutines are called 'local declarations' in what follows.
  2. It allows for one level above the subroutine level: the 'global declarations'. These are usual Fortran declaration statements which are written once in front of a set of subroutines in a file. The global declarations are valid within all of these subroutines.
  3. In order to exclude an obvious source of errors, it is not allowed to re-declare global variables locally.
  4. In order that the compiler can recognize global declarations and distinguish them from local declarations within a main program, the PROGRAM statement is mandatory.
  5. There is also one extra level of declarations below the subroutine level which allows for dynamic storage allocation (see 2.7.4 for the ALLOCATE-ENDBLOCK construct).
Some examples might illustrate the use of global declarations.
  1. 'Standard' example. Without use of global declarations, a set of routines would look like:
          PROGRAM P        \
          INCLUDE 'I.FOR'  |
          INTEGER II,JJ    |  Main program
          REAL ...         |
          ...              |
          END              /
    
          SUBROUTINE S     \
          INCLUDE 'I.FOR'  |
          DATA A /1.0/     |  Routine 1
          ...              |
          END              /
    
          FUNCTION F(X)    \
          INCLUDE 'I.FOR'  |  Routine 2
          ...              |
          END              /
    
    where the INCLUDE file contains e.g.
          COMMON /A/ A,B,C
          COMMON /S/ I,J,K
          PARAMETER (PI=3.14)
    
    Using global declarations, one can write it as follows:
          INCLUDE 'I.FOR'     Global declarations
    
          PROGRAM P        \
          INTEGER II,JJ    |
          REAL ...         |  Main program
          ...              |
          END              / 
    
          SUBROUTINE S     \
          DATA A /1.0/     |  Routine 1
          ...              |
          END              /
    
          FUNCTION F(X)    \
          ...              |  Routine 2
          END              /
    
    Notes:
    1. The PROGRAM statement is required in RTF68K. Without it, the local declarations of P would betaken as global, and the first executable statement of P would be flagged as an error.
    2. Local declarations stay within each routine.
    3. Global declarations of course need not be contained in INCLUDE files. The contents of I.FOR could be given in place of the INCLUDE statements in the example above.
    4. The global variable A has been preset with DATA locally. This is possible but bad style. The preferred method would be to give the DATA statement globally.

  2. In the above example, A is a global variable. Redeclaration of A like (referring to the example above)
          FUNCTION F(X)
          DIMENSION A(100)
          ...
          END
    
    is illegal and flagged as an error.

  3. Global variables should be normally in COMMON blocks, but this is not necessary in principle. Consider, again referring to the example (a), the following contents of I.FOR:
          REAL A,B,C
          INTEGER I,J,K
          PARAMETER (PI=3.14)
    
    Still, the variables A,B,C,I,J,K and the constant named PI are globally defined. However, the variables reside now not in the memory for COMMON blocks, but in the space drawn from the stack when the program is initialized. Thus, the connection to separately compiled files which are linked with the example file is no longer as obvious as would be the case for COMMON blocks. In fact, non-COMMON global variables from separate files will normally overlap in memory, unless special care is taken.

    The use of such global variables should thus be restricted to system libraries.

  4. Also other kinds of declarations may be written in the global declarations part, e.g. the special ones
          EQUIVALENCE (ILOOP,D7)
          KEEP D7
    
    The effect is that ILOOP is now a globally declared variable which resides in register D7 for speed, and is saved/restored on each routine's entry/return (see chapter 2.5.8).
Apart from the scope of a declaration, the scope of validity of the value carried by a declared variable has to be considered. The former has to do with the static nesting of blocks as written down in the program source, the latter deals with the dynamic nesting of blocks during execution. Fortran usually disallows recursivity, i.e. a subroutine cannot call itself (neither directly or indirectly through another routine). At least, results of such calls are inpredictable. On the other hand, the standard says that the values of local variables of a subroutine are lost when you leave the routine and enter it again, unless the variables are in COMMON or SAVE. Nevertheless, many Fortran implementations leave those values unchanged. RTF/68K offers an option (SAVE=ALL) to guarantee this, too.

Now note the following: recursivity has the consequence that the values of local variables MUST be lost when leaving the routine. Re-entrancy, which is a requirement in interrupt-driven real-time environments, is a more general case of recursivity. Thus, if you want to use RTF/68K in the field it was made for, the values of local variables are for sure lost when leaving a routine (COMMON or SAVE variables must be used with great care in cases where re-entrancy is required). The reason is of course that space for local variables has to be allocated on the stack, and this space is re-used for other variables after leaving the routine.

One further consequence is on DATA statements: variables which are preset with DATA cannot be on the stack. They must be in COMMON or SAVE. Routines which alter the values of DATA variables are not reentrant. If the values are not altered, the variables are constants and should better be declared with PARAMETER.

2.4.2 PARAMETER declarations

PARAMETER declarations assign names to arithmetic, logical, or character string constants. These names can be used in place of the constant, e.g. also as array bounds in DIMENSION declarations. They offer the possibility to define a constant, which is used in many places within a program, in just one central place. Whenever a value is really constant during program execution, PARAMETER is very much preferred over DATA statements.

PARAMETER statements may be given globally or locally. Like on the VAX, PARAMETER statements may be written with (standard) or without parentheses, e.g.:

      PARAMETER (pi=3.14159,max=500,assert='YES')
or
      PARAMETER pi=3.14159,max=500,assert='YES'
The data type associated with the name is always the data type of the constant, e.g. REAL for pi, CHARACTER*3 for assert in the example above. Please refer to 2.2 for the various forms of integer constants. One may also state the data type in addition with a type declaration, but only prior to the PARAMETER statement. The type declaration, if given, must agree completely with the constant used in the PARAMETER statement. E.g.,
      REAL pi; INTEGER max; CHARACTER*3 assert
      PARAMETER (pi=3.14159,max=500,assert='YES')
is legal, while
      REAL pi,amax; CHARACTER*5 assert
      PARAMETER (pi=3.14159,amax=500,assert='YES')
contains two errors.

2.4.3 Data type declarations

The data types available have already been listed in 2.3. above. Consider <type> to be one of
INTEGER, INTEGER*1, INTEGER*2, INTEGER*4, DOUBLE INTEGER, BYTE
REAL, REAL*4, REAL*8, DOUBLE PRECISION, DOUBLE REAL
LOGICAL, LOGICAL*1, LOGICAL*2, LOGICAL*4
CHARACTER, CHARACTER*n, CHARACTER*(*)
Then a data type declaration has the form ([..] denotes optional syntax elements):
      <type> <dcl>[,<dcl>...]
where <dcl> is one of:
      <name> [<arraybounds>]       or
      @<name> [<arraybounds>] 
The former is the standard Fortran-77 variable or array declaration, while the latter declares a pointer-based variable or array (@ is the symbol for 'pointer to' or 'address of'). <name> is a usual Fortran name of any length and may, apart from uppercase letters and digits, also contain lowercase letters, underline, and dollar characters.

Pointer-based variables have their address assigned or changed during execution of the program; please refer to 2.4.11 and 2.7 for further explanation. Note here that in case of pointer variables or arrays of any data type, four bytes are always reserved for the address of the variable. No space is allocated for the values. The data type, and accordingly the word size, is an attribute of the value of a variable and has nothing to do with its address.

2.4.4 DIMENSION declarations

This declaration is in principle redundant in Fortran because array bounds may also be given together with other declarations, e.g. of data type. The syntax is:
      DIMENSION <vdcl>[,<vdcl>...]
where <vdcl> is one of
      <name> <arraybounds>         or
      @<name> <arraybounds>
The former is the standard Fortran-77 array declaration, while the latter declares a pointer-based array.

The array bounds have the usual form:

      (<bounds>[,<bounds>...])
with the following choices for <bounds>:
      <integer constant>                     or
      <integer constant:integer constant>    or
      <integer variable>
In RTF/68K, up to five <bounds> are permitted; i.e. tensors of rank five can be handled.

The third of the above forms of <bounds> provides variable array bounds. While normally restricted to formal arguments of routines, RTF/68K allows variable bounds also for pointer-based arrays; see the example of chapter 1.1 above. The mechanism is clear: bounds may be variable because in both cases memory is not allocated during compilation, but during program execution.

2.4.5 COMMON declarations

As in the standard, COMMON declarations are used to make storage blocks accessible globally for several routines. Storage allocation is usually performed by the linker. In addition, RTF allows to allocate storage under the programmer's control: either to a fixed address known when writing the program or to a variable address known only during execution. For the latter, see also the RECORD declaration below.

The syntax of COMMON declarations is on of

      COMMON <dcl>[,<dcl>...]
      COMMON // <dcl>[,<dcl>...]
      COMMON /<base>/ <dcl>[,<dcl>...] .
See 2.4.3 above for <dcl>.

The first and second forms both denote 'blank COMMON'. The latter form denotes 'named COMMON' as usual, but in RTF is also used for 'absolute COMMON' and 'pointer-based COMMON', depending on the form of <base> which is one of:

      <name> or
      <integer constant>                 or
      @<name> 
The first form results in standard 'named COMMON' and space is allocated by the linker which will normally give a base address to the COMMON block at link-time. If the option COMMON=INDIRECT is chosen, or if <name> appears in an INDIRECT declaration, the <name> form has the same effect as the @<name> form (see below). Still, the operating system takes care of space allocation, but this can then be delayed until load-time (necessary e.g. on the Macintosh).

The second form results in 'absolute COMMON'. Here, the programmer determines the base address of the COMMON block at programming time. The block is by this means placed into special hardware, e.g. an extra fast memory module. The integer constant may also be a PARAMETER declared before the COMMON declaration, e.g.

      Parameter (VectorBase='100000'X)
      Common /VectorBase/ IVector(0:255)
or just
      Common /'100000'X/ IVector(0:255) .
The system gets no notice about absolute COMMONs.

The third form denotes 'pointer-based COMMON'. Here, the allocation of space for the COMMON block can be made more dynamically - at load-time or at run-time, depending on how the pointer is declared.

If @<name> is not declared explicitely somewhere, then the system will take care of space allocation at load-time. For the user, this looks much like ordinary named COMMON, apart from the fact that the base address can still be modified at run-time. The <name> form with option COMMON=INDIRECT, or <name> appearing in an INDIRECT declaration, has the same effect as the @<name> form without explicit pointer declaration. In both cases, the base address is held in a storage word addressed relative to the program counter at the end of a program module for non OS-9, or in the VSECT for OS-9. Thus for non OS-9 care must be taken when changing this storage word: the base address will be altered only in this program module. Other, separately compiled modules will not be affected (an appropriate warning is given by the compiler). Briefly speaking, @<name> without explicit pointer declaration is meant for load-time allocation of space as required by some operating systems, and not primarily for run-time allocation under the user's control.

If, however, the pointer is declared explicitely before the COMMON declaration, or if the name of the COMMON appears in a TEMPLATE declaration, the operating system does not get notice of the COMMON block, and the user has to allocate space at run-time. This is done with an assignment statement for the pointer, e.g.:

      Integer @Struct,CpuIndex,CpuBase
      Common /@Struct/ Xlow(1000),Xup(1000)
      ...
      @Struct=CpuIndex*'800000'X+CpuBase
      Xup(I)=XLow(I)+123.4
This can be applied for shifting data structures around in memory. The purpose of the RECORD statement (see below) is exactly the same. The 'scope' of the space allocation is the same as the scope of the declaration of the pointer; i.e. if @Struct in the above example is a local variable of a routine, the entire pointer-based COMMON is defined only in this routine. On the other extreme, if @Struct is itself in an ordinary COMMON block, then the definition is global - i.e., the effect of the @Struct=... statement is global.

2.4.6 SAVE declarations

According to the standard, the SAVE declaration is used to maintain the values of variables when leaving and reentering routines. For many Fortran implementations, this is achieved even without SAVE. In RTF, however, and in full accordance with the standard, SAVE is required if values of local variables of a routine are to be maintained during leave from that routine. Without SAVE, those variables would reside on the stack for re-entrancy and hence their values are lost on exit from the routine. COMMON variables are always maintained.

The syntax of the SAVE declaration is:

      SAVE <dcl>[,<dcl>...]        or
      SAVE /<name>/ .
Note that local variables can be preset with DATA statements in RTF only if they appear in a SAVE declaration. There are no such restrictions for COMMON variables.

A global SAVE for all local variables can be enforced with the option SAVE=ALL. This may be useful when porting programs from the usual (but non-reentrant) Fortran environments to RTF.

2.4.7 EQUIVALENCE declarations

EQUIVALENCE declarations are the Fortran programmer's way to control storage allocation of variables. In the standard, they can be used to control memory addresses of variables relative to each other; e.g. variables of different data types and formats can share the same storage. As such, EQUIVALENCE is considered bad practice. In RTF, EQUIVALENCE can (and is meant to) be used to control the absolute positions rather than the relative positions of variables, although the latter is also possible.

The syntax of EQUIVALENCE in RTF is:

      EQUIVALENCE (<name>,<base>)      or
      EQUIVALENCE (@<name>,<base>) 
where <name> is the name of a variable to which storage is not allocated by other means than the EQUIVALENCE statement (e.g., COMMON variables not allowed here). <base> may be one of
      <variable ref>                          or
      <integer constant>                      or
      <register name>                         or
      @<name> 
<variable ref> is the name of a simple variable, array, or an array element reference. This form is used for the standard EQUIVALENCE statements. Note that only pairs of arguments may appear in RTF.

<integer constant> is used to give a fixed absolute address to a variable. This is useful for accessing special hardware locations easily, e.g.:

      Integer*1 IOReg
      Equivalence (IOReg,'FF0021'X) 
      ...
      IOReg=15
<register name> is used to force a variable in a register of the CPU or a coprocessor. The following symbols are reserved words when appearing as the second argument of EQUIVALENCE:
D0, D1, D2, D3, D4, D5, D6, D7 for the data registers of the 68K processor
A0, A1, A2, A3, A4, A5, A6, A7 or SP for the address registers of the 68K processor
F0, F1, F2, F3, F4, F5, F6, F7 for the floating point registers
- valid for the 68881/2 coprocessor,
the 68040 processor and software emulation
SR for the status register of the 68K processor
Variables of any data type (1, 2, or 4 bytes long) except CHARACTER, as well as pointers, may reside in the data or address registers. Typically, values should be kept in data registers, and pointers in address registers.

The floating point registers are useful only for variables of type REAL.

Variables EQUIVALENCEd with the status register must be declared INTEGER*2.

The purpose of putting values or pointers in registers is threefold:

  1. a considerable gain in speed for frequently used variables or pointers,
  2. a way of interfacing e.g. with operating systems that expect or deliver parameters in registers,
  3. a way to keep floating point results in extended precision (64 mantissa bits instead of the 53 available in double precision).

Note that registers used by the programmer via EQUIVALENCE, unlike registers allocated automatically by the compiler, are not saved on entry and restored on exit from the routine that uses them. The KEEP directive (see below) has to be used for this purpose if it is desired to keep register contents unaltered for the outside world. This is a must for interrupt service routines and normally true also for usual routines.

@<name> is used for EQUIVALENCEing with pointers. This is useful e.g. when making an equivalence with a formal argument which is passed by reference. Note that whenever variables are pointer-based, only ther pointer may be used in EQUIVALENCE because the memory allocation of the values is not known at compile time.

Examples of EQUIVALENCE:

  1. ...the standard way:
          INTEGER*1 I1(4); INTEGER*4 I4
          COMMON /XX/ I4
          EQUIVALENCE (I1,I4)
    
  2. ...with an absolute address:
          INTEGER*2 RegisterFile(0:15)
          EQUIVALENCE (RegisterFile,'3400006'O)
          ...
          RegisterFile(0)=1
    
  3. ...with data registers:
          Function Dot(N,A,B)
          Integer A(N),B(N),N,I,S
          Equivalence (I,D7),(S,D6)
          Keep D7,D6
          S=0
          Do I=1,N
          S=S+A(I)*B(I)
          EndDo
          Dot=S
          End
    
  4. ...with address registers in addition:
          Function Dot(N,A,B)
          Integer A(N),B(N),N,I,S,AA(N),BB(N)
          Equivalence (I,d7),(S,d6),(@AA,a4),(@BB,a3)
          Keep a3,a4,d6,d7
          @AA=@A
          @BB=@B
          S=0
          Do I=1,N
          S=S+AA(+)*BB(+)
          EndDo
          Dot=S
          End
    
    Note the special array indexing used in the formula. Writing S=S+AA(I)*BB(I) or S=S+A(I)*B(I) would both give exactly the same result, but the 'autoincrement' form chosen is by far the fastest. It is only available if the pointer to the array resides in an address register. The compiler generates the post-increment mode of addressing of the 68K processor for it. The code generated from S=S+AA(+)*BB(+) is (option CPU=68020):
          MOVE.L (A4)+,D2
          MULS.L (A3)+,D2
          ADD.L D2,D7
    
    Using as an array reference e.g. BB(-) results in the pre-decrement addressing mode. In the above example, it is in principle not necessary to copy the pointer of array A into an address register. The first two formal arguments of routines are copied to address registers automatically by the compiler in order to have fast access to them (unless option REGUSE=OFF is used). Thus also the special addressing mode is available for A. But beware: the pointer is of course changed by using the special addressing mode! This does no harm in the example because the pointer is no longer used afterwards.

  5. ...with floating point registers:
          Equivalence (X,F7),(X2,F6),(V,F5)
          Keep F5,F6,F7
          ...
          X2=X**2
          V=exp(X2-sin(X2)*cos(X)+sinh(X))
    
    The code generated for the above formula is in the case of the MC68881/2 coprocessor (option FLOAT=HARD):
          FMOVE.X FP6,FP0
          FSIN.X FP6,FP1
          FCOS.X FP7,FP2
          FMUL.X FP2,FP1
          FSUB.X FP1,FP0
          FSINH.X FP7,FP1
          FADD.X FP1,FP0
          FETOX.X FP0,FP1
          FMOVE.X FP1,FP5
    
    The advantages are obvious from this code: (1) the coprocessor is utilized optimally. No operand moving between CPU and coprocessor takes place; (2) extended precision (64-bit mantissa) is maintained throughout the calculations, and when storing the results.

  6. ...with the status register:
          Equivalence (CpuStatus,SR)
          Integer*2 CpuStatus
          ...
          If(CpuStatus.lt.0) ...          ! check if in TRACE mode
    
    Note that access to the status register is only allowed in supervisor mode. The PRIORITY=... statement (see below) can be used if only the priority part of the status word should be affected.

    Also note that there is no KEEP for the SR. Explicit save/restore to e.g. a local variable must be used for temporary changes to the status register. In interrupt service routines, the status before interrupt occurance is restored automatically on routine exit.

  7. ...with formal arguments:
          Subroutine S(X)
          Real X(100); Integer IX(100)
          Equivalence (@IX,@X)
          ...
          Subroutine T(%VAL(Y))
          Real Y; Integer IY
          Equivalence (IY,Y)
          ...
    
    Note that EQUIVALENCE (IX,X) which semantically looks the same would not be accepted by the compiler. Only items which occupy memory with addresses known at compile time can be equivalenced; in the first example above, those items are the pointers to X and IX, while in the second example, the values of Y and IY.
As can be seen from the examples above, registers used by the programmer with EQUIVALENCE should be allocated starting from the upper end of the available sets of registers, i.e. starting with D7, D6... for the data registers, A4, A3... for the address registers, and F7, F6... for the floating point registers. A7, A6, and A5 are reserved for use by the system (thus there is often a shortage of address registers). The compiler starts allocating registers from the lower ends of the sets. If a clash between user's and compiler's allocation occurs, a warning is given.

2.4.8 EXTERNAL declarations

EXTERNAL declarations are normally used to state that a name refers to a subroutine or function in cases where this is not obvious from the context, i.e. when such names are used as actual arguments of routines. This is also the case in RTF.

In addition to that, also variables and even entire COMMON blocks can be made to refer to external objects (e.g., data which are located at an entry point of an assembler routine). This corresponds to the IMPORT and EXPORT variables known in Pascal. In order to distinguish those variables from standard EXTERNALs and to provide an access method by the standard linkers, they have to be pointer-based, i.e. their names have to be preceded by '@' in the EXTERNAL declaration.

Examples:

      External @Iarr
      Integer Iarr(20,20)
      ...
      Iarr(5,5)=0

      External @Com,@I
      Common /@Com/ X,Y,Iz(100)
      ...
      X=Y+Iz(I)
In these examples, the addresses of the external variables (Iarr and X,Y,Iz,I) are equated by the linker to entry points in other code modules.

2.4.9 DATA statements

DATA statements belong to the declarations part of a routine and are used to preset variables with values once prior to execution of the user's code. Values may be changed afterwards; if not, i.e. if the variables are in fact constants, PARAMETER declarations should be used whenever possible (e.g. not for arrays). DATA statements result either in blocks of data put into the appropriate storage location by the loader, or in pieces of code executed after loading and before the user's program is entered, depending on the operating environment.

DATA statements must be put between the last of the other declarations and the first executable statement, or statement function definition.

In RTF, DATA statements have no purpose in addition to the standard one. Instead, there are some restrictions for the variable list. The syntax in RTF is:

      DATA <var>/<const list>/[[,]<var>/<const list>...]
<var> stands for a simple variable, an array name, an array element reference, or a pointer. Note that only one item, not a list, is allowed for <var>. Implied-Do lists are not allowed. Moreover, <var> must be declared SAVE if it is a local variable. Only global, COMMON, or SAVE variables can be preset with DATA.

Example:

      Subroutine Junk
      Logical FirstTime
      Integer Arr(0:9,2)
      Save FirstTime, Arr
      Data FirstTime/.true./, Arr/10*0,10*1/
      ...
is legal in RTF, while omission of the SAVE or writing Data FirstTime,Arr/.true.,10*0,10*1/ are not.

2.4.10 INCLUDE directive

The INCLUDE directive is an extension to the standard present in most Fortran implementations. It is useful for inserting a piece of source text from a different file, especially one which contains all COMMON declarations used by a set of subroutines.

The syntax in RTF is:

      INCLUDE '<filename>'                   (VAX style)
The syntax and interpretation of <filename> depends on the operating system under which RTF is executed.

2.4.11 Pointers

Pointers contain the addresses of variables rather than the values, which are carried by the variables themselves. The concept of accessing values indirectly through pointers is not unknown to Fortran users; it is used all the time when replacing the formal arguments of a subroutine definition with the actual arguments of a subroutine call. By means of the subroutine call, the programmer determines the addresses of the formal arguments. This is the only occurence of pointers in Fortran.

The additional feature available with pointer variables as in RTF (or C, Pascal) is that the programmer has full control on the addresses of variables, not only of formal arguments. Many illustrations for pointers were used already on the previous pages; in summary, pointers are adequate for variables or data structures whose position in the 68K's address space is determined only at run-time. Paragraph 2.7. is devoted to the use of pointers. Only one important rule that must be obeyed for declaring pointer variables is stated here:

If the address of a variable is to be changed in the executable part of a routine, the variable must be either declared as a pointer variable, or not declared at all.

Examples:

      Integer @ITDC
      @ITDC=ICamAd(B,C,N,A,F,T)
      JTDC=ITDC
or just
      @ITDC=ICamAd(B,C,N,A,F,T)
      JTDC=ITDC
are both correct and give the same result. It is not correct to declare ITDC without the pointer mark '@':
      Integer ITDC
      @ITDC=ICamAd(B,C,N,A,F,T)
      JTDC=ITDC
The compiler gives an error message in this case for the second statement which tries to modify the address of a variable which is not pointer-based, but has a fixed address assigned by the compiler.

(Semantic meaning: in the above examples it is assumed that the CPU has memory-mapped access to a CAMAC system, and that the function ICamAd returns the address of a CAMAC object with given branch B, crate C, station N, subaddress A, function F, and wordsize T. Once the address is assigned to the pointer variable ITDC, the access to it, i.e. the I/O to the CAMAC system, is as simple and as fast as the access to a normal variable in memory.)

Note also that there exists in RTF an extension to the ASSIGN statement which is normally used to handle addresses of statement labels. Here it can be used for addresses of variables or array elements as well. This provides the functionality of the 'abbreviations' known from the transputer language OCCAM. For example,

      ASSIGN A(I,J,K) to B(0)
      B(0)=B(1)-B(-1)
has the effect that a linear array B is defined which has the same data type as A and where the element B(0) has the same address as the element A(I,J,K). B can then be used as a shorthand form for A(I,J,K), B(1) for A(I+1,J,K), etc. This speeds up access very much in cases where A(I,J,K) and elements with constant offset relative to A(I,J,K) are accessed frequently - especially if @B is EQUIVALENCEd with an address register.

2.4.12 RECORD declarations

The pointer-based COMMON blocks have been described already in paragraph 2.4.5; a RECORD is exactly the same as a pointer-based COMMON whose pointer is explicitely declared. Syntax:
      RECORD /<name>/ <dcl>[,<dcl>...]
<name> is the name of a variable not declared so far, or declared as a pointer variable. Included in the latter case are formal arguments of routines. As mentioned earlier, the purpose of RECORDs is to have data structures that can be imposed on any block of storage, just by setting the address of the RECORD properly.

Examples:

  1. ...the pointer is not declared elsewhere, hence it is allocated on the stack (local variable):
          Subroutine Junk
          Record /D/ Flags,X,Y,Z; Integer Flags; Real X,Y,Z
          @D=...                           ! set base address of RECORD
          If(Btest(Flags,0)) X=...
    
  2. ...the pointer is declared as a COMMON variable:
          Subroutine Junk
          Common /Bases/ @D                ! assume @D is set elsewhere
          Record /D/ Flags,X,Y,Z; Integer Flags; Real X,Y,Z
          If(Btest(Flags,0)) X=...
    
  3. ...the pointer is declared as a formal argument:
          Subroutine Junk(D)               ! @D supplied by subroutine call
          Record /D/ Flags,X,Y,Z; Integer Flags; Real X,Y,Z
          If(Btest(Flags,0)) X=...
    
In the second example, it would be illegal to omit the '@' in the COMMON declaration.

2.4.13 INDIRECT and TEMPLATE declarations

The INDIRECT and TEMPLATE declarations offer another way to make COMMONs pointer-based. They allow this without using the '@' mark explicitely and without affecting all COMMONs globally, as with the option COMMON=INDIRECT. The INDIRECT declaration can be used as a global declaration, or locally in each subroutine, preceding the COMMON declarations. Syntax:
      INDIRECT <name> [,<name>...]
<name> is the name of a COMMON block in a COMMON declaration later in the code. INDIRECT <name> together with COMMON /<name>/ has the same effect as COMMON /@<name>/.

Example:

Indirect aa,bb
Common /aa/ x,y,z
Common /bb/ i,j,k
Common /cc/ o,p,q
is the same as
Common /@aa/ x,y,z
Common /@bb/ i,j,k
Common /cc/ o,p,q
The TEMPLATE declaration is similar to INDIRECT, but in addition it prevents the automatic allocation of space. Thus it works as if the pointer to the COMMON was declared explicitely. Syntax: TEMPLATE <name> [,<name>...] <name> is the name of a COMMON block in a COMMON declaration later in the code. TEMPLATE <name> together with COMMON /<name>/ has the same effect as COMMON /@<name>/ and explicit declaration of the @<name> in another COMMON, such that the pointer is a global variable as in the INDIRECT case.

Example:

Template aa,bb
Common /aa/ x,y,z

Common /bb/ i,j,k

Common /cc/ o,p,q
is the same as
Common /@aa/ @a
Common /@a/ x,y,z
Common /bb/ @b
Common /@b/ i,j,k
Common /cc/ o,p,q
COMMON indirections can be hidden this way, letting the source appear more standard. Mixture of INDIRECT and TEMPLATE is allowed, and both pointers refer to the identical block of memory.

2.5 Subroutines and functions

This chapter is intended to provide details of the implementation with respect to subroutine and function definitions and calls rather than the language-guide type of information on this topic. Also, the extensions available for interrupt handling etc. are described.

2.5.1 General overview

Passing of arguments from the calling program to a subroutine or function can be done in RTF by three different means:
by VALUE the value of a variable, constant, or expression is passed;
by REFERENCE the address of a variable, array, or auxiliary variable containing the value of a constant or expression is passed;
by DESCRIPTORthe address of a descriptor block which contains further information is passed (details are found below).
The default method is passing by reference for all objects except for character variables or character expressions which are passed by descriptor. The default can be overcome as follows:
  1. Reference arguments may be passed by value. In the call as well as in the subroutine/function declaration, they have to be prefixed by a "#" for this purpose, or surrounded by "%val(...)" as on the VAX. This calling method is restricted to simple variables and constants. It is slightly faster than call by reference and may be necessary for compatibility with routines written in other languages calling or called by RTF routines.
  2. Descriptor arguments may be passed by reference. Only in the call, they have to be prefixed by "#@" (i.e. value of address of), or better surrounded by "%ref(...)" as on the VAX. Then the address of the first character instead of the address of the descriptor is passed. In the called routine, the argument cannot be CHARACTER in this case.
Trailing actual arguments may be omitted (short parameter list) if precautions in the called routine are taken.

All arguments are transferred via the stack. Arguments are pushed on the stack before the call and removed from the stack after the call by the calling program.

The first two arguments (i.e., their addresses when called by reference) are copied to address registers inside of the called routine in order to have fast access to them. With the option REGUSE=OFF, this optimization is switched off. This may be useful in cases where the compiler runs out of address registers within subroutines.

Function results are returned via the register D0 if the value of the result fits into 32 bits (so far, everything except type CHARACTER). Otherwise, the stackframe contains an address, provided by the caller, which points to where the value has to go.

When passed by reference, actual arguments may be simple variables, expressions, arrays (those three not of type CHARACTER), EXTERNALs, and constants (including string constants). Formal arguments may be simple variables, arrays (both not of type CHARACTER), or formal subroutines or functions. Passing by descriptor applies for actual arguments which are simple variables or expressions of type CHARACTER, and any formal arguments of type CHARACTER. When passed by value (i.e. with the '#' in front or inside %val(...)) actual arguments may be simple variables, constants, or expressions. Formal arguments may then only be simple variables. Type CHARACTER is not allowed for call by value.

Side exits from subroutines are denoted in the standard way by "$" or "*"

Secondary entry points are defined by ENTRY as usual. In addition, entry points coded with embedded assembler statements (and thus invisible to the compiler) can be declared with the "ASSEMBLER name" statement (see below).

If inside of a function definition its declared name appears with an argument list, e.g in expressions, this results in a (legal) recursive call of the function. Occurence of the function name inside the function without an argument list is handled in the standard way, i.e. as the value of the function identifier.

All registers explicitely used by the compiler are saved during subroutine calls. The registers referenced by the user with EQUIVALENCE (variable,register) are, however, not automatically saved. The KEEP statement must be used to save these registers unless the routine is intended to change one or all of these registers.

Subroutines may be statically designated to handle certain interrupts. This is requested with the "INTERRUPT vectornumber" statement which has to follow immediately the subroutine statement. The specific meanings of vectornumber values is hardware dependent. The effect is to modify the appropriate interrupt vector cell during initialisation such that it points to the routine.

The current priority of a task may be changed with the statement PRIORITY=prio, where prio is a constant between 0 and 7. The user should be aware of the effects resulting from priority changing. In routines serving interrupts, the priority is automatically reset to its value prior to the interrupt when returning from the routine.

The code generated by RTF for subroutine definitions and calls is compatible with the 'CERN calling conventions for 68k processors' with the exception that registers are saved by default inside of the called routine instead of by the caller. This scheme is necessary for direct interrupt server routines. A compilation option, REGSAVE=OUTSIDE, forces RTF to stick to the CERN scheme also for register saving. In addition to, but compatible with the CERN scheme, the actual number of arguments is passed to the called routine via D0 to be able to handle short argument lists. For the option CODE=OS9, register assignments stick to OS-9 rules instead of CERN conventions; the actual number of arguments may then be passed via the condition code register, CCR.

2.5.2 Stack assignment during calls

In the following, AG denotes the base register for the global/static variables, and AL denotes the base register for local variables. For all options but OS-9, AG is A5 and AL is A6. For OS-9, ist is just the other way around: AG is A6 and AL is A5.

Actual parameters (addresses, 32-bit values) are pushed on the stack by the calling program in the reverse order of the argument list. Note that pushing uses pre-decrement addressing mode which lowers the stack pointer. After that, the call (with assembler instruction JSR) pushes the return address on the stack. In the called routine, the LINK instruction saves the address register AL on the stack and reserves space for local variables. Local variables are addressed relative to AL, i.e., with the d(AL) mode. Then, the entry address to the routine and an all-zero word are stored at locations -4(AL) and -12(AL) (-8(AL) is unused), resp., providing information for the symbolic debugger and traceback. This is done only if the option DEBUG=ON is chosen. Following these words, the contents of the necessary data-, address-, and floating point registers are saved within the local space. Local program variables are allocated from -204(AL) downwards.

It is normally the calling program's responsibility to remove the arguments from the stack after return from the call, by moving the stack pointer with an LEA d(A7),A7 instruction. If the called routine takes a side exit, i.e. it does not return to the proper point of the calling sequence, it removes the arguments itself. In this case, short argument lists are not allowed, because the number of arguments stated in the declaration is removed.

If the called routine is a function, it returns its result via D0. If the result occupies 4 bytes or less, the value is returned directly in D0. If the result occupies more than 4 bytes, the value is returned to the memory location pointed to by D0. This is the case for type CHARACTER functions only. Note that those functions are thus not able to obtain the actual number of arguments (except for OS-9).

The stack layout after entry into the called routine (more precisely, after registers are saved and debug information is stored) is shown in the figures below. If you require access to the stackframe from Fortran, use the predeclared INTEGER*4 array STACKFRAME with indices given as below; e.g., STACKFRAME(21) contains the return address.

Summary of register usage in connection with calls:

D0: Scratch register; on entry, contains number of actual arguments, or address of first parameter if OS-9. On exit, contains result if function call, else the value on entry.
D1:
..
D7:
}Working registers. For OS-9, D1 contains address of 2nd parameter.
A0: Address of first actual argument (if >= 1 formal arg. present and REGUSE=ON; else working register).
A0: Address of second actual argument (if >= 2 formal args. present and REGUSE=ON; else working register).
A2:
A3:
A4:
}Working registers.
AG: Global space pointer (global user variables and system variables, d(AG) ).
AL: Local space pointer (local user variables inside routine ,d(AL) with negative offset).
A7: Stack pointer.
Non OS-9 stackframe:
OS-9 stackframe:
Format of character string descriptors:
Whenever a character VARIABLE is referenced, a descriptor of this variable is set up in the following format (3 longwords occupied):
For example, assume CHARACTER*10 A,B. Then the descriptors look as follows for various character expressions:
In calls, the address of the descriptor of character variables or expressions is given, with a descriptor flag bit of this address set to 1. The marker bit is bit 31 usually, or bit 0 if the option CODE=OS9 is chosen; this is the default for OS-9 systems. This allows to distinguish between descriptors and normal addresses. For character CONSTANTS, the address of the first character is given, with the descriptor flag bit cleared as usual. Character constants are null terminated. As soon as an expression is formed with constants, e.g. 'ABC'//'DEF', however, a descriptor is set up.

2.5.3 ENTRY specification

The ENTRY specification is used to provide alternative entry points into subroutines and functions; the same is true for RTF.

The formal arguments of an ENTRY can differ from those of the main entry point in number, names, and order. In RTF, when a formal argument has the same name as one of the main entry or a previous ENTRY, a warning is given. After the ENTRY, the ordering of arguments stated there is maintained statically.

Example:

      Subroutine Alfa(A,X,Y)
      Real A,B,X,Y
      A=X-Y
      Entry Beta(B,Y,X)                ! CAUTION X and Y change roles
      B=X-Y
      End
In this odd example, the following happens when entry Alfa is called with CALL ALFA(O,P,Q). First, O is assigned the value P minus Q. Then (after skipping the non-executable ENTRY specification) O is assigned the value Q minus P. That is of course not what you want - so be aware of this implicit EQUIVALENCE scheme when using ENTRY!

2.5.4 ASSEMBLER entry specification

This extension to Fortran is provided for pieces of code written in embedded assembly code. Other than writing the entry point declaration also in embedded assembly, the RTF ASSEMBLER entry specification makes it an 'official' entry point which fully sticks to the rules imposed by the interactive linker, symbolic debugger, and traceback. Formal arguments are not allowed at ASSEMBLER entry points.

Note: A sequence of embedded assembler statements MUST be preceded by a dummy Fortran statement, otherwise the embedded code may be inserted at a wrong place. The ASSEMBLER entry specification fulfills this need.

Example:

      Subroutine Dummy
      Assembler Kill
+     ILLEGAL
      Assembler Fiddle
+     MOVE.L #4711,A7
+     RTS
      End

2.5.5 Statement functions

Statement functions conform to the standard. They are implemented not like macros which are inserted at every call point, but are entered with JSR and left with RTS much like external functions. Only the way of argument passing is faster: the arguments of a statement function as well as its value are local variables of the program unit containing the statement function. In effect, arguments are passed by value. Also, time for saving and restoring registers is minimized.

2.5.6 Intrinsic functions and subroutines

The following paragraph describes the functions and subroutines which are recognized by the compiler as non-external and are handled in a special way. The purpose is twofold: a) run-time efficiency, and b) special handling of involved data types (generic functions).

2.5.6.1 Intrinsic functions

Note that the routine names specified in this chapter cannot act as substitutions for dummy routines in subroutine or function calls; i.e. they cannot be declared EXTERNAL. For example,
      CALL SUB(X,ABS)                  is NOT allowed.
They may, of course, be used in expressions which are used as actual arguments:
      CALL SUB(ABS(X))                 is allowed.
The reason is that fast in-line code is generated for the routines described in this chapter rather than subroutine/function calls. For some of the routines, this is only true if certain compiler options are chosen.

2.5.6.1.1 Bit manipulation functions

Note for the following that bits are numbered from 0 to 31 on the 68k, 0 being the least significant bit. This is important for the functions IBSET, IBCLR, IBCHG, BTEST, and BITFLD where reference to absolute bit numbers is made. Also JBYT and JBIT use bit numbers, but starting from1 for the least significant bit, for CERN compatibility.
i = IAND(j,k)
i = AND (j,k)
I is the bit-by-bit product of j and k. Both must be INTEGER (any size), as is the result.

Example: MANTISSA=AND(IREAL,'7FFFFF'X).

i = IOR (j,k)
i = OR  (j,k)
I is the bit-by-bit sum of j and k. Both must be INTEGER (any size), as is the result.

Example: PATTERN=IOR(PATTERN,ENDFLAG).

i = IEOR(j,k)
i = EOR (j,k)
i = IXOR(j,k)
i = XOR (j,k)
I is the bit-by-bit difference of j and k. Both must be INTEGER (any size), as is the result.

Example: ITOGGLE=EOR(ITOGGLE,1).

i = INOT(j)
i = NOT (j)
I is the bit-by-bit inverse of j. The data type of the result is that of j.

Example: ZERO=IAND(MASK,NOT(MASK)).

i = IBSET(j,k) I is the same as j but the k-th bit set. The data type of the result is that of j. The data type of k must be INTEGER (any size). K is evaluated modulo 32.

Example: REALMINUS=IBSET(REAL,31).

i = IBCLR(j,k) I is the same as j but the k-th bit cleared. The data type of the result is that of j. The data type of k must be INTEGER (any size). K is evaluated modulo 32.

Example: REALABS=IBCLR(REAL,31).

i = IBCHG(j,k) I is the same as j but the k-th bit inverted. The data type of the result is that of j. The data type of k must be INTEGER (any size). K is evaluated modulo 32.

Example: REALINV=IBCHG(REAL,31).

i = ISHFT(j,k) I is j shifted by abs(k) places to the left (if k positive) or right (if k negative). The bits shifted out are lost and zeros are filled in. The data type of the result is that of j. The data type of k must be INTEGER (any size). K is evaluated modulo 32.

Example: IEXPO=ISHFT(IREAL,-23).

i = LSHFT(j,k)
i = ISHFTL(j,k)
Both are similar to ISHFT, but k should be positive and a leftshift is always done.

i = RSHFT(j,k)
i = ISHFTR(j,k)
Both are similar to ISHFT, but k should be positive and a rightshift is always done.
Note that the data type of RSHFT is not REAL despite of the name.

if(BTEST(j,k)).. BTEST is a logical function which is TRUE if the k-th bit of j is set. The data type of k must be integer (any size). K is evaluated modulo 32.

Example: IF(BTEST(STATUS,12)) CALL ALARM.

i=BITFLD(j,o,l)
i=IBITS(j,o,l)
Both extract a field of bits, from bit number o (offset) to o+l-1, i.e. length l, from j, and presents it right justified with leading zeros, such that bit number o of j becomes bit number 0 of i etc. The processor's BFEXTU instruction is used. The data type of the result is always INTEGER*4.

Example: IEXPO = BITFLD(X,23,8).

See also inline subroutines BITFINS, SBYT, and SBIT, and subroutine MVBITS in appendix A 2

i = JBYT(j,o1,l) Similar to BITFLD, but bit numbers run from 1 to 32.

Example: IEXPO = JBYT(X,24,8).

i = JBIT(j,o1) Same as JBYT, but implies length l=1.

i = SWAP_B(j) The least significant two bytes of j are exchanged, i.e. the least significant word is byte swapped. The most significant word is not affected. The data type of the result is that of j; should be 2 or 4 bytes long.

Example: I1243=SWAP_B(I1234).

i = SWAP_W(j) The two words of the longword j are exchanged, i.e. the longword is word swapped. The data type of the result is that of j; should be 4 bytes long.

Example: I4321=SWAP_B(SWAP_W(SWAP_B(I1234))).

y = F_TO_VAX(X) X is converted from IEEE floating point to VAX floating point representation (offset of 2 in the exponent). X can be any 4-byte quantity; the bit pattern should denote a floating point number. The type of the result is that of x. The conversion uses integer arithmetic only.

Example: VAX1 = F_TO_VAX(1.0).

y = VAX_TO_F(X) The inverse of F_TO_VAX.

Example: F1 = VAX_TO_F('40800000'x).

2.5.6.1.2 Other functions that produce in-line code

i = MOD(j,k) I is j modulo k. If k is a constant power of two, an AND is carried out, otherwise a divide. J and k must both be INTEGER (any size), as is the result.

i = IABS(j) I is the absolute value of j. J must be INTEGER (any size), as is the result.

r = ABS(s) R is the absolute value of s. S must have an arithmetic (any size) data type. The data type of the result is REAL.

r = DABS(d) R is the absolute value of d. D must be REAL*8, as is the result.

i = IFIX(s)
i = INT(s)
i = IDINT(s)
I is s, converted to INTEGER by truncating to the nearest integer closer to zero. S must have an arithmetic (any size) data type. The type of the result is INTEGER.

r = FLOAT(s)
r = REAL(s)
r = SNGL(s)

R is s, converted to REAL. S must have an arithmetic (any size) data type. The type of the result is REAL.

r = DFLOAT(s)
r = DBLE(s)
R is s, converted to REAL*8. S must have an arithmetic (any size) data type. The type of the result is REAL*8.

i = ICHAR(c) I is the binary representation of the first ASCII character of the string c. The result is type INTEGER. C must have type CHARACTER.

Example: LOWERA=ICHAR('a').

c = CHAR(j) C is the ASCII string representation of the binary value j. J must have type INTEGER (any size). The result is type CHARACTER*1.

Example: CHARSET(I:I)=CHAR(I).

if (Lcc(c,d))... Lcc is a logical value stating the result of lexical comparison of two CHARACTER strings c and d. cc may be one of LE, GE, NE, LT, GT, or EQ.

Note: Lcc(c,d) generates the same code as c.cc.d .

if(OWNER(sem)).. OWNER is a access control primitive which uses the TAS instruction of the processor to test and set a semaphore. It is a logical function which is .TRUE. if the semaphore was free, i.e. the calling program owns it after the call. Sem must be variable (not expression) of any data type; only its first byte is accessed. A natural choice would be INTEGER*1. Releasing the resource then works with sem=0.

Example:

      DO WHILE(.NOT.OWNER(BRANCH))
      CALL WAIT
      ENDDO
      CALL ACCESS
      BRANCH=0

2.5.6.1.3 Standard functions

r = func(s) Func is the value of the standard function acting on the argument s. S must have an arithmetic (any size) data type. Func stands for:

SQRT, SIN, COS, TAN, ASIN, ACOS, ATAN, EXP, EXP10, LOG, LOG10, SINH, COSH, TANH, ATANH,

- here the result is REAL, or REAL*8 is s is REAL*8
any of the above preceded with D, e.g. DSQRT,
- here the result is REAL*8
or ALOG, ALOG10 (same as LOG, LOG10).

r = RNDM(j) RNDM is a random generator with uniform distribution in (0,1). J must be declared as INTEGER*4 J(2). The two values should be initialized and are updated in each RNDM call. They can be saved as a starting point for later use. The type of the result is REAL. RNDM provides a period length of 2**64.

r = RNORM(j) RNORM generates random numbers with normal distribution (derived from 12 calls to RNDM). Call similar to RNDM.

i = LEN(c) LEN calculates the number of characters in the character string expression c.

Example:

      CHARACTER*128 CH
      ...
      NONBL=LEN(CH(1:-1))              ! length without
      ...                              ! trailing blanks
i=INDEX(c1,c2) INDEX calculates the character index in the character string expression where the character string expression c2 starts. Zero is returned if c2 is not found in c1.

Example:

      I=INDEX(FILE,'.')
      IF(I.NE.0) THEN
      FILE1=FILE(:I)//'FOR'
      ELSE
      FILE2=FILE//'.FOR'
      ENDIF
i = NINT(x) I is x, rounded to the nearest integer. X must be type REAL. The type of the result is INTEGER. Not a generic function.

Example: IROUND=NINT(R).

i = INCHR(lu) Single character input without wait. Lu is the logical unit (INTEGER*4). I (INTEGER*4) is zero if no character is present; else it has the integer value of the ASCII character entered.

Example:

      do forever
      i=inchr(1)
      if(i.ne.0) then
      call action(i)
      else
      call background

2.5.6.1.4 Word size modifiers

These serve as a shorthand alternative for mixtures of data type and EQUIVALENCE statements (especially when accessing the same hardware in different modes). Note that, if used on the left side of assignments, they are outside the Fortran standard.
i = BYTE(j)
BYTE(j) = i
Regardless of the data type specification of j, only its first data byte is read or written, resp.; i.e., the result is as if j were declared as INTEGER*1. If BYTE is used for reading (on the right hand side or in arithmetic expressions), its argument may be a constant.

i = WORD(j)
WORD(j) = i

The same for the first 2 bytes (word) of j; like INTEGER*2 declaration.

i = LONG(j)
LONG(j) = i

The same for the first 4 bytes (longword) of j; like INTEGER*4 declaration.
Caution: Note the quite different (peek/poke type) meaning of the above intrinsic names in ABSOFT Fortran. Use EQUIVALENCE with absolute addresses or pointer variables if the effect of the ABSOFT BYTE, WORD, or LONG is desired.

2.5.6.2 Intrinsic subroutines

Some in-line procedures have been added which are invoked with CALL statements. They perform simple, often-used operations at maximum speed without any subroutine call overhead. - In particular, one class uses instruction sequences which have 'looping capability' on the 68010, acting on blocks of data. - Other classes act as 'hardware subroutines' by activating peripheral processors or coprocessors for 68020/30.

2.5.6.2.1 Looping mode subroutines

Note: The word sizes may apply for various data types; e.g. _MOVL may be used for INTEGER*4, LOGICAL*4, and REAL*4 data, _CMPB may be used for INTEGER*1 and LOGICAL*1, etc. The DBcc instruction is used by the compiler; nevertheless, there is no 16-bit restriction to the block length.
call _MOVL(s,d,l)
call _MOVW(s,d,l)
call _MOVB(s,d,l)

call UCOPY(s,d,l)

Moves a block of l words (size L or 4 bytes, W or 2 bytes, B or one byte each) from s to d. UCOPY is synonymous with _MOVL. As moving starts from the low address, in case of overlap s must begin at a lower address than d.

Example:CALL _MOVB(ARRY(1),ARRY(1001),1000).

call _SETL(v,d,l)
call _SETW(v,d,l)
call _SETB(v,d,l)
Writes the value v (word size as above) into all l components of the block d. See also subroutine UZERO in appendix A 2.

Example: CALL _SETL(3.14,PIARR,LPIA)

call _CMPL(s1,s2,l)
call _CMPW(s1,s2,l)
call _CMPB(s1,s2,l)

Compares two blocks of l words each (word size as above), s1 and s2. Comparison starts from the low addresses and terminates when either two words are not equal or all l words are done. The result appears in the condition code register of the processor and can be checked subsequently.

Example:

      CALL _CMPW(A,B,10000)
      IF(.EQ.) THEN
        CALL IDENTICAL
      ELSE IF(.LT.) THEN ! i.e. A < B
        ...
As an alternate notation, one can also use the following aliases:
MOV_L, MOV_W, MOV_B
SET_L, SET_W, SET_B
CMP_L, CMP_W, CMP_B
instead of, resp.
_MOVL, _MOVW, _MOVB
_SETL, _SETW, _SETB
_CMPL, _CMPW, _CMPB

2.5.6.2.2 Hardware subroutines

  1. FASTBUS. A subset of the standard Fastbus routines is implemented as a coprocessor for 68020. They are enabled by the option FB=HARD (see above). Then statements of the following form result in generating essentially one F-line coprocessor instruction instead of a subroutine call. Please refer to FASTBUS specifications for the meaning of the routines:

    call Fx(p1,p2,...)

    with x = RD, WD, RC, WC,
    RDM,WDM, RCM, WCM,
    RDSA, WDSA, RCSA, WCSA,
    RDB, WDB, RCB, WCB,
    RDBM, WDBM, RCBM, WCBM,
    WAI, MOVES, WRT, RRT

    Example: CALL FRD(IRET,ID,PA,SA,BMOD,DATA)

  2. As the source of the compiler is easy to modify, more sets of special hardware routines can be made available for Fortran use without runtime overhead.

2.5.6.2.3 Bit field subroutines (only for options CPU=68020, 68030, 68040)

call BITFINS(i,j,o,l) Extracts from i a field of length l bits, starting from bit number 0 (the least significant one), and inserts it into bits o to o-l+1 of j, such that bit number 0 of i becomes bit number o of j etc. The other bits of j remain unchanged. This uses the processor's BFINS instruction.

Example: CALL BITFINS(IEXPO,R,23,8)

See also: intrinsic functions BITFLD / IBITS, JBYT and JBIT, and subroutine MVBITS in appendix A 2.

call SBYT(i,j,o1,l) Similar to BITFINS, but bit numbers run from 1 to 32.

call SBIT(i,j,o1) Same as SBYT, but implies length l=1.

2.5.7 Obtaining the actual number of arguments

As inidcated above, the caller passes the number of actual arguments to the called routines if both Then the number of arguments is in register D0 (or CCR if OS-9) after entering the called routine. The called routine may transfer the number of arguments to a variable by using
      CALL NUMPAR(var)                 or
      CALL NOARG(var)
as the first executable statement. The compiler then generates inline code for that of the kind
      MOVE.L D0,var
If the call is made without parameters, i.e.
      CALL NUMPAR()                    or
      CALL NOARG()
no code is generated.

If the call is completely left out, however, RTF generates code to check if the actual number of arguments is the same as the formal number of arguments:

      CMP.W #formal,D0
      BEQ *+4
      JSR _BADPAR
This check may be suppressed with the option CHECK=OFF, or with a call to NUMPAR/NOARG without arguments as described above.

Calling NUMPAR or NOARG other than in the first executable statement results in a normal call to a user-supplied routine.

2.5.8 KEEP directive

The KEEP directive should accompany EQUIVALENCE with registers. Other than registers which are allocated by the compiler itself, the user-declared registers are not automatically saved at entry and restored at exit of the routine using them. If the contents of user declared registers is to be preserved for the outside world (which is normally the case, and is a must for interrupt handler routines), the names of those registers have to appear in the KEEP directive. Otherwise, the routine exits with the value of the register(s) altered - maybe useful only as an odd way of passing results.

Also when modifying registers in embedded assembly code parts, these registers should appear in KEEP.

The registers accessible to the user by this means are the processor data registers D0-D7, the processor address registers A0-A7, and the floating point coprocessor data registers F0-F7. The processor status register SR, which is accessible with EQUIVALENCE, cannot appear in KEEP, however.

Example:

      Function ISum(IA)
      Integer*2 I,IA(100); Integer ISum,IS
      Equivalence (I,d7),(IS,d6)
      Keep D7,d6
      IS=0
      Do I=1,100
      IS=IS+IA(+)
      EndDo
      ISum=IS
      End
If one omits the KEEP in this example, the function should be better called ITrouble - because it will affect the caller's registers D6 and D7 in an uncontrolled manner!

2.5.9 INTERRUPT and EVENTFLAG directives

As mentioned previously, RTF subroutines can be used as interrupt handlers without any operating system overhead. For this purpose, the entry address of the subroutine is written into the appropriate longword of the CPU's interrupt vector. On occurance of the interrupt signal (an external hardware signal or software trap), the CPU's microcode saves the current CPU status word and program counter (or more for some special interrupts) on the stack and jumps directly to the subroutine's entry point. The saving of the rest of the CPU's current context (registers) is done by the subroutine internally. Thus, it takes typically only 20 usec on a 10 MHz 68000 from the interrupt to the first useful instruction of the subroutine (i.e., after the register saving).

The exit from an interrupt routine is special as compared to a normal subroutine: not only the old program counter, but also the old CPU status word are restored from the stack. Thus the return from interrupt has to use the assembler instruction RTE instead of RTS.

Both setting up the interrupt vector location and preparing the proper return instruction is done by the INTERRUPT directive. It has to be the first of the declaration statements, i.e. it has to be placed directly after the subroutine statement. After the keyword INTERRUPT, either a integer constant in the range 2 to 255 or a '*' must follow. In the first case, the interrupt vector location with the given constant as index is set to the routine's entry address during program initialization, much as with a DATA statement. The interrupt vector location is not touched during initialization in the second case, but this is then left for runtime (see subroutine ACTIVATE below). In both cases, the proper return from interrupt is generated.

Examples:

Subroutine Iresp
Interrupt 200                          ! set vector 200 to addr(Iresp)
Byte reg
Equivalence (reg,'ff3000'x)
reg=0                                  ! 1st executable instruction
...
End                                    ! exit with RTE

Program Main
External Iresp1
...
Call Activate(200,Iresp1)              ! set vector 200 to addr(Iresp1)
...
End

Subroutine Iresp1
Interrupt * 
Byte reg
Equivalence (reg,'ff3000'x)
reg=0                                  ! 1st executable instruction
...
End                                    ! exit with RTE
In the first example, the interrupt vector is set automatically during initialization, while this is done explicitely by the main program in the second example.

If one uses the keyword EVENTFLAG instead of INTERRUPT, the compiler generates an RTR instruction instead of RTE. A vector number is not allowed then, only the '*'. This may be useful for returning from asynchronous event handlers supported by some operating systems (OS-9, VersaDOS).

Example:

Common /Flags/ IDone
Program Main
External Iresp2
...
Call Enable(Iresp2)            ! tell operating system to enable handler
...
End
Subroutine Iresp2
Eventflag * 
IDone=1                        ! 1st executable instruction
...
End                            ! exit with RTR or through operating system
Refer to the appendix A 5.5 for a more detailed, OS-9 specific example.

2.5.10 CPU time required for subroutine calls

The caller has to push the addresses of the N actual arguments onto the stack (PEA intructions), move N to D0 (MOVEQ), perform the jump to subroutine (JSR and JMP), and to clean up the stack after return (ADDQ). The called routine has to setup the local variable area (LINK), save registers (MOVEM), optionally check the actual number of arguments and stack limit (two times CMP, Bcc), then after execution of the user's code restore the registers (MOVEM), remove the local variable area (UNLK), and return (RTS).

On a 68000 processor, a subroutine call requires thus the following number of clock cycles:

96 + 16*(n+m) + 28*c

where n is the number of actual arguments, m is the number of registers to be saved inside of the routine, and c is 1 if the option CHECK=ON is chosen, 0 else. For n=2, m=4, c=0 this sums up to 192 clock cycles or roughly 20 µsec for a 10 MHz 68000.

2.5.11 Type conversions for integer arguments

There are cases where the conformation of actual and formal subroutine arguments is not evident: for integer constants and integer expressions containing INTEGER*2 parts. For example, in
      INTEGER*2 I,J
      ...
      J=I+1
      ...
the expression I+1 is treated as INTERGER*2, i.e. as a 16-bit word. The same is true in
      Options MULDIV=SHORT
      ...
      INTEGER*4 I
      INTEGER*2 J
      ...
      J=I/5
      ...
for the expression I/5 as a consequence of the 68000's DIVS instruction, while in the case I/4 (use of shift) the type is INTEGER*4.

The features mentioned above are justified by optimizing criteria but are not at all obvious to the user, and hence could lead to arbitrary results if such expressions are used as actual subroutine arguments.

Therefore the following scheme is used to arrive at definite data types for integer actual arguments.

  1. Simple variables and array elements are passed with the type imposed by type declaration or implication as usual.
  2. Integer constants and integer expressions other than (1) are passed as INTEGER*4 when the option INTSIZE=4 (default) is chosen.
  3. Integer constants and integer expressions other than (1) are passed as INTEGER*2 when the option INTSIZE=2 is chosen.
A similar difficulty occurs in principle also for LOGICAL variables. However, due to the representation of logical values with the topmost byte only, confusion of LOGICAL*1, *2, and *4 actual arguments has no effect.

2.6 Other language elements

2.6.1 Arithmetic, logical, and character string expressions

Expressions consist of the basic operands: constants, simple variables, array elements, and values returned by functions. The operands are connected by operators which obey certain precedence rules. These rules may be overridden by parentheses. There are different operators for the three classes of expressions: arithmetic, logical, and character string. Expressions cannot contain mixtures of the classes - that is, arithmetic operands are connected by arithmetic operators to other arithmetic elements only. In the same way logical operands and operators remain isolated, and character string operands and operators. The exception are relational operators which derive a logical value from a pair of arithmetic or character expressions. Of course, function and subroutine calls allow explicit transitions between the classes; ICHAR(c) and CHAR(i) are examples. In addition, the EQUIVALENCE declaration opens room for unrecommended tricks to circumvent the class separation.

2.6.1.1 Arithmetic expressions

The biggest and most frequently used class is arithmetic. It offers three data types: integer, real, and in RTF also pointers which are handled as integers. Mixed mode arithmetic means that different data types of a class are mixed within an expression. Rules have to be applied for automatic type transformation. Whenever two operands of different data type are connected, the one with the lower data type is transformed to the higher data type. The hierarchy of arithmetic data types is (same level within one line):

Highest: Real, Real*4 and also Real*8 in RTF
  Integer, Integer*4 and also Pointers in RTF
  Integer*2
Lowest: Integer*1, Byte.

RTF has several intrinsic functions for explicit arithmetic type transormations: FLOAT for transformations to Real, and IFIX, INT, NINT for transformations to Integer. BYTE, WORD, LONG also yield type Integer, but they do not perform a type transformation. They rather give the original bitpattern of the operand, interpreted as type Integer, much as an EQUIVALENCE does.

The arithmetic operators are: unary, exponential, multiplicative, additive. The precedence rules say: operations with the strongest binding first, unless parentheses contradict. Within an expression, proceed from left to right. The hierarchy of binding is (same level within one line):

Strongest: (...) (parentheses)
  + (unary plus), - (unary minus), @ (address of)
  ** (exponention)
  * (multiplication), / (division)
Weakest: + (addition), - (subtraction).

Other basic operations like bit handling, ABS, MOD, etc. look like functions, but are implemented as fast inline code in RTF. Function values are of course one entity regardless of the number of arguments, like expressions within parentheses.

2.6.1.2 Logical expressions

Logical data could be represented by one bit. Due to the processor instruction set (Scc instruction), one byte is used instead - the most significant byte, regardless of the data size (LOGICAL*1, *2, *4). Thus there is no need for conversion between the different sizes. The canonical forms are an all-ones byte (hexadecimal FF) for .TRUE. and an all-zero byte for .FALSE. (hexadecimal 00), respectively. When in a data register (e.g. as result of a logical function), all 32 bits of the register are ones ore zeros.

The logical operators are: unary, and, or. The precedence rules say: operations with the strongest binding first, unless parentheses contradict. Within an expression, proceed from left to right. The hierarchy of binding is (same level within one line):

Strongest: (...) (parentheses)
  .NOT. (unary negation)
  .OR. (logical or)
  .AND. (logical and)
Weakest: .EQV. (logically equal), .NEQV. (logically different).

Function values are of course one entity regardless of the number of arguments, like expressions within parentheses. Relational operators are binary operators which transform arithmetic or character operands into logical without having the form of a function. These have all stronger binding that the logical operators above. They are:

.LT. (less than)
.LE. (less or equal)
.EQ. (equal)
.NE. (not equal)
.GE. (greater or equal).
.GT. (greater than).

When used with charaters, the equivalent lexical comparison functions can be used alternatively; the generated code is the same as for the relational operators. Example: c1.lt.c2 is equivalent to LLT(c1,c2), and both have type logical.

In RTF, the relational operators can be used without operands; they then reflect the current condition codes in the processor status register, as a result from a previous operation. In this sense, they act much like a logical function, the implied argument being the condition code. When without operands, also the following are allowed:

.CARRY. (carry condition set)
.OVERFLOW. (overflow condition set)

2.6.1.3 Character string expressions

Character strings are represented by a string of bytes and a length information. In character constants, the length information is carried by a null byte (hexadecimal 00) as terminator, otherwise a descriptor which is stored in memory separately from the string itself contains the length. The bytes may contain any information, not just ASCII characters, with the restriction that character constants cannot contain the null byte. As each character of a string is always one byte long, there are no size transformations. The data type CHARACTER denotes a single character, CHARACTER*n denotes a string of n characters.

The character operators are: substring, concatenation. The precedence rules say: operations with the strongest binding first, unless parentheses contradict. Within an expression, proceed from left to right. The hierarchy of binding is (same level within one line):

Strongest: (...) (parentheses)
  (l:u) (substring extraction)
Weakest: // (concatention).

The substring indices l or u may be omitted as usual. As an extension known from NORD Fortran, RTF uses the special value -1 as a shorthand for suppression of leading blanks (l = -1) or trailing blanks (u = -1). Example: LEN(C(:-1)) is the lenght of C without trailing blanks.

Function values are of course one entity regardless of the number of arguments, like expressions within parentheses.

2.6.2 Assignment statements

Assignment statements have a left hand side (left of the assignment operator =) and a right hand side. The data types of left and right must be compatible, i.e. arithmetic types of any kind can be assigned to arithmetic of any kind only, and the same is true among logical and among character. Again, pointers belong to the arithmetic types. Type transformations take place automatically when necessary, and lead to the data type of the left hand side.

Regarding pointers, they can only appear as a left hand side if the variable pointed to has not been declared so far, or has been explicitely declared as a pointer based variable. In other words, you cannot change addresses which the compiler has automatically given to variables.

2.6.3 Label and variable ASSIGN statements

Label ASSIGN statements are used in Fortran in connection with assigned GOTO statements. The syntax is:
      ASSIGN <label> TO <variable>
where <label> is the label of an executable Fortran statement in the same program unit. <variable> is a simple variable or an array element of type INTEGER*4. The effect is that the address of the labelled statement is stored in the variable. Later, this address may be used in GOTO <variable> which results in an indirect jump.

In RTF, there exists an extension to the ASSIGN statement. It can be used to access addresses of variables or array elements, in addition to addresses of statement labels. It then acts as a dynamic EQUIVALENCE performed at run-time. Syntax:

      ASSIGN <variable> TO <base>
where <variable> is a simple variable or array element reference of any data type. <base> has the form:
      <name>                     or
      <name>(<const>) .
<name> may be a name not declared so far, or a name declared as a pointer variable or linear pointer-based array.

In both cases, a pointer-based, linear array of the same data type as <variable> is declared. In the first case, the element name(1) gets the same address as the variable, while in the second case, name(const) gets the same address as the variable. <const> is an integer constant.

This provides the functionality of the 'abbreviations' known from the transputer language OCCAM. Examples:

  1.       ASSIGN A(I,J,K) to B(0)
          B(0)=B(1)-B(-1)
          B(2)=0
    
    has the same effect as
          A(I,J,K)=A(I+1,J,K) - A(I-1,J,K)
          A(I+2,J,K)=0
    
  2.       EQUIVALENCE (@XX,A4),(I,D7); KEEP A4,D7
          ....
          ASSIGN X(1,J,K) TO XX
          S=0
          DO I=1,N
            S=S+XX
            XX(+)=0
          ENDDO
          
    has the same effect as
          S=0
          DO I=1,N
            S=S+X(I,J,K)
            X(I,J,K)=0
          ENDDO
    
In both cases, much speed is gained. In the first example, one can also speak of an 'abbreviation', while this is not really the case in the second example. In general, ASSIGN to variables pays in cases where the same array element or elements with constant offset relative to each other are accessed frequently.

2.6.4 DO loops

Standard Fortran allows only one form of DO loops:
      DO <label> [,] <variable>=<startexpr>,<endexpr>, [,<stepexpr>]
        [<statements>]
<label> <statement>
where <label> is the label of an executable Fortran statement later in the same program unit, <variable> is a simple variable or array reference of arithmetic data type, and <...expr> are arithmetic expressions. Note that RTF allows only integer data types here. The range of a DO loop may be empty, in which case the statements following the DO are not executed. The sign of the optional step expression determines whether the variable is increased or decreased on each iteration.

There are additional forms of DO statements available in RTF:

      DO [FOR] <variable>=<startexpr>,<endexpr>, [,<stepexpr>]
        [<statements>]
      END DO

      DO WHILE {<logical expression>}
        [<statements>]
      END DO

      DO UNTIL {<logical expression>}
        [<statements>]
      END DO

      DO FOREVER
        [<statements>]
      END DO
Note that ENDDO can be used instead of END DO.

The first form above (block DO) is an extension known from VAX Fortran and is useful for more structured programming, avoiding statement labels much like with the block IF.

The second form is an extension known from VAX Fortran. The loop is executed while the logical expression is .TRUE. (maybe zero times). Loop control takes place at the beginning of the loop. The third form also allows loop control according to a logical expression, but here the loop is executed at least once until the logical expression is .TRUE.; loop control takes place at the end of the loop. The last form is equivalent to DO WHILE (.TRUE.) and also results in the same code.

2.6.4.1 BREAK and NEXT loop control statements

In addition to any executable statement, the special control statements BREAK and NEXT are also allowed within the range of a DO loop. BREAK terminates the loop by transferting control to the next statement right after the end of the loop. NEXT proceeds with the next iteration of the loop. Both statements act only on the innermost loop they are contained in, i.e. it is not possible to jump over more than one level of loop nesting. An error message is given when BREAK or NEXT are used outside of any loop.

2.6.5 IF statements

Three kinds of conditional statements are available in Fortran: arithmetic, logical, and block IF statements. The syntax is for:

arithmetic IF:

      IF (<arithmetic expr>) <label>,<label>,<label>
logical IF:
      IF (<logical expr>) <statement>
block IF:
      IF (<logical expr>) THEN
        [<statements>]
      [ELSEIF (<logical expr>) THEN
        [<statements>] ]
      [ELSEIF (<logical expr>) THEN
        [<statements>] ]
        ...
      [ELSE
        [<statements>] ]
      END IF
where <arithmetic expr> is an expression of an INTEGER or REAL data type, <label> is a label of an executable Fortran statement in the same program unit, <logical expr> is an expression of type LOGICAL, <statement> is a legal Fortran statement and <statements> is one or more legal Fortran statements.

Arithmetic IF is considered old-style Fortran and bad practice. In the case of block IF, one must be careful not to confuse an ELSE IF clause with ELSE, followed by a different IF statement on a new source statement line; even more so in the case of the potentially free-format RTF: ELSE IF(...) on one line is the end if clause, while ELSE followed by IF(...) on a new source line is an ELSE clause, containing a new IF statement. END IF and ENDIF, ELSE IF and ELSEIF are synonymous.

2.6.6 GOTO statements

There are three kinds of GOTO statements in Fortran: unconditional, assigned, and computed GOTO. The syntax is for:

unconditional GOTO:

      GOTO <label>
assigned GOTO:
      GOTO <integer var> [ [,] <label>,<label>,... ]
computed GOTO:
      GOTO (<label>,<label>,... ) [,] <integer expr>
where <label> is a label of an executable Fortran statement in the same program unit, <integer var> is a simple variable or array element of type INTEGER*4 which previously became defined with a label ASSIGN statement, and <integer expr> is an expression of an integer data type.

If a label list is provided in the assigned GOTO, it has only the purpose of documenting potential GOTO target labels in RTF; the compiler does not interpret the labels. The variable has to contain the address of the target label, which is then reached by an indirect JMP instruction.

Assuming a list of n labels is provided in a computed GOTO, the integer expression should have a value between 1 and n. If the value is outside of this range, the GOTO is not executed, and the statement following the GOTO is executed next.

GOTO and GO TO are synonymous.

2.6.7 Input/Output statements

Formatted input:
      READ(unit,fmt[,ERR=label][,END=label]) [,] ilist
      READ fmt,ilist
      ACCEPT fmt,ilist
Unformatted input:
      READ(unit[,ERR=label[,END=label]) [,] ilist
Formatted output:
      WRITE(unit,fmt[,ERR=label][,END=label]) [,] olist
      PRINT fmt,olist
      TYPE fmt,olist
Unformatted output:
      WRITE(unit[,ERR=label[,END=label]) [,] olist
Unit is the logical I/O unit. It may be *, an integer constant or expression, an array name, character variable name, or a pointer. All of the latter three modes provide internal conversions. The * denotes the default I/O unit (e.g. the terminal).

Ilist contains simple variables or array elements, array names, or implied loops made out of them. Olist contains, in addition to ilist elements, arithmetic, logical, or character string expressions (including constants).

If the last character of a formatted output record is a "$", and the output goes to a terminal, the record is output without this last "$" and without CR/LF. If the last character is a "?", the action is similar but the "?" is still output. Both are useful when prompting for input from a terminal.

FORMAT statements are standard. Static formats (supplied at compile-time) and variable formats are supported. Format specifications, with parentheses and between quotes, may also be contained in the I/O statement itself.

Example:

      type '(I5,Z9)',j1,j2 
and
      type 10,j1,j2
   10 format(I5,Z9)
are equivalent.

The following format field descriptors are supported:

I decimal representation of integer data with default width (I12) on output or free-format input
Iw same with width w on input and output
Iw.n same, but at least n non-blank digits (leading zeros) on output
Z hexadecimal representation of integer, real, or logical data with default width (Z9) on output or free-format input
Zw same with width w on input and output
O octal representation of integer, real, or logical data with default width (O12) on output or free-format input
Ow same with width w on input and output
B binary representation or integer, real, or logical data with default width (B33) on output or free-format input
Bw same with width w on input and output
L representation of logical data (T for .true. and F for .false.) with default width (T2) on output or free-format input
Lw same with width w on input and output
A ASCII representation of character, integer, real, or logical data. The width depends on the size of the data.
Aw same with width w on input and output
F fixed-point representation of real or real*8 data with default width (F10.3) on output and free-format input
Fw.d same with width w and d digits after the decimal point on input and output
E normalized exponential representation of real or real*8 data with width (E12.3) on output or free-format input
Ew.d same with width w and d digits after the decimal point on input and output
D or G same as E
Dw.d or Gw.d same as Ew.d
X one blank on output, skip one position on input
Tn tabulation to column n; fills with blanks on output, skips on input
'...'character constant (quoted) only for output
nH...character constant (length n) only for output
(..) encloses group of format descriptors

All of the above descriptors may be preceded by a repetition factor. Further format elements are:
, delimiter between format elements
/ end-of-record mark; serves also as delimiter

OPEN and CLOSE have the following form:

      OPEN([UNIT=]lu,[FILE=]filename 
          [,STATUS=status] [,SIZE=filesize]
          [,CARRIAGECONTROL=carriagecontrol] 
          [,ACCESS=access] [,FORM=format]
          [,ERR=errorlabel])

      CLOSE([UNIT=]lu [,STATUS=status],[ERR=errorlabel])
Both forms result in according requests to a the local file system or a file system remote on the host computer. Filename, status, carriagecontrol, access, and form are character string expressions. If several paramters are given, note that their order has to be as stated above. Also, only one of the two parameters STATUS or SIZE (SIZE implies STATUS='NEW'), and only one of the three parameters CARRIAGECONTROL, ACCESS, or FORM can be used in one OPEN statement.

The values of these expressions, even if constants, are not checked by the compiler. They are interpreted by the local or host computer's file system. Useful values are for

Status:'OLD', 'NEW', or 'UNKNOWN'for Open
'KEEP' or 'DELETE'for Close
Size: (any integer)
Carriagecontrol: 'NONE', 'LIST', or 'FORTRAN'
Access: 'READ', 'WRITE', 'APPEND', 'DIR', or 'EXEC'
Form: 'FORMATTED' or 'UNFORMATTED'.
Defaults depend on the file system.

After a user-controlled error exit (END or ERR labels provided), the global predefined INTEGER*4 variable IOSTATUS contains a system-dependent error code. This can then be checked further by the user program.

Example:

      OPEN(10,'xxx.yyy',status='old',err=99)
      ...
   99 type *,'OPEN error',iostatus 
The statements
      BACKSPACE lu
      REWIND lu
      ENDFILE lu
complete the set of I/O statements available in RTF/68K.

INQUIRE is not implemented.

2.6.8 PRIORITY statement

This statement may be used to change the running priority of the CPU, e.g. in order to allow/disallow interrupts up to a certain interrupt priority. The statement affects the priority part of the processor status register and is thus only allowed in supervisor mode. Form:
      PRIORITY = <octal constant>
where <octal constant> is an integer constant in the range 0-7. PRIORITY is a reserved word in the above context.

For example, the statement is useful to lower the priority to allow interrupts early in re-entrant interrupt handlers of certain device drivers. Another example is the protection of critical code parts by raising the priority to 7 temporarily (it should be kept in mind that this scheme is incomplete in multiprocessor setups where semaphores maybe required in addition or instead).

2.6.9 CACHECONTROL statement

This statement has been added to allow dynamic changes to the mode of the instruction cache of 68020/30 processors. This statement affects the cache control register (CCR) and is only allowed in supervisor mode. Also, the option CPU=68020 or 68030 must be selected. Form:
CACHECONTROL = <control constant>
where <control constant> is a 4-bit integer constant. Useful values on a 68020 (only instruction cache) are:
0disable cache
1enable cache
3freeze and enable cache
8clear and disable cache
Normally, the cache should always be enabled. - Please refer to the 68030 user's manual for the extra functionality of the data cache integrated on the 68030 chip, which is controlled with other bits of the CCR.

2.7 Use of pointers, registers, and absolute addresses

The word 'pointer', the symbol '@' for 'address of', and special forms of EQUIVALENCE declarations with processor registers D0-D7, A0-A7, F0-F7 have been used many times in the previous chapters, specifically in 1.2, 2.4.5, 7, 8, 11-13 and 2.5.8. Examples have been given to clarify these extensions over standard Fortran found in RTF. Only a short summary of all that and some extra hints are given in the following paragraphs.

2.7.1 Subroutine arguments as an example and comparison with C

Subroutine calls are an example where in Fortran the binding of objects (formal variables, formal subroutines etc.) to memory locations (addresses) is done at run-time: the calling routine passes the address of the object to the called routine which uses it as a pointer to the passed argument. Thus the formal argument is internally defined as a pointer based object, and the pointer is adjusted at run-time to the address of the actual argument. This method, used by standard Fortran only implicitely, can be used in RTF explicitely as well, by means of pointer declarations.

Remember that the symbol '@' means 'address of' an object in RTF, much as the '&' in C language. However, the syntax used in C for pointers and values is quite different from RTF. This shows up in declarations and when accessing values based on pointers.

Example in C:
main()
{
    int *i,j,*k;
    i=0xffa00000;
    *i=0;
    j=*i;
    k=i+1;
    k=&j;
}
Equivalent in RTF:
      Program Test

      Integer @i,j,@k
      @i='ffa00000'x
      i=0
      j=i
      @k=@i+1
      @k=@j
      End
The declaration in C says that i is a pointer to int and *i is an int value, while the declaration in RTF says that @i is a pointer to integer and i is an integer value. Consequently, in the subsequent statements, in C i refers to the pointer and *i refers to the value, and in RTF @i refers to the pointer and i refers to the value. J refers to an int value in both cases. In the last statement, the address of j is accessed. The symbol '&' is used for that purpose in C, while in RTF, again the symbol '@'. In both cases the address of j cannot be changed because j is not declared as a pointer.

Note that RTF offers no proper pointer arithmetic as C does. (@i+1) in the RTF example is ((address of i) plus one), i.e. an odd byte address pointing to the second byte within i, while (i+1) in the C example is (address of (next object after i)), i.e. the address of i plus 4 (i.e. the size of i). Pointers are handled exactly like integers in RTF, and are type-compatible with them.

In general: in C the name of a variable declared with '*' refers to a pointer, and the name of a variable declared without '*' refers to a value. In RTF, the name of a variable always refers to a value and the name preceded by "@" always refers to a pointer.

Subroutine calls can also serve as an example of processor register usage. RTF puts the addresses of the first two arguments into address registers for efficient access to these arguments, and other Fortran compilers may do more of this kind implicitely. In RTF, one can use processor registers also explicitely, similar to C, but even using specific registers instead of selecting just the 'storage class' register.

Example in C:
test1(i,j)
register int *i,*j;
{
    *j=*i+1;
}
The same in RTF:
      Subroutine Test1(i,j)
      Integer i,j
    c Equivalence (@i,a0),(@j,a1)
      j=i+1
      End
result in very similar assembler code. RTF does implicitely what the extra declaration statement which is commented out would do explicitely, namely, hold the pointers to i and j in address registers a0 and a1, respectively.

2.7.2 Obtaining and changing addresses

The symbol '@' stands for the operation 'address of' the object it precedes. It may appear on the left side of an assignment statement, or in expressions. In both cases, the '@' can only act on objects which have addresses. These are:
ObjectDeclaration Use of pointer
simple variableInteger ij=@i
array elementReal a(5,5)j=@a(i,2)
arrayReal a(5,5)j=@a
EXTERNAL objectExternal subj=@sub
pointer to RECORDs or pointer-based COMMONsCommon /@c/ x,yj=@c
where all except EXTERNAL may be local, global, formal arguments, or elements of COMMONs or RECORDs. This list excludes constants, expressions like (i+1), and names of normal COMMON blocks.

If the @ appears on the left side of an assignment statement, the object it acts on must have a variable address. These are:

ObjectDeclarationUse of pointerUse of object
simple pointer-based variableInteger @i@i='f000'xi=0
pointer-based arrayReal @a(5,5)@a='f000'xa(i,j)=0
pointer to EXTERNAL objectExternal @sub
@sub='f000'xcall sub
orExternal @i
Integer i(100)
@i='f000'xi(10)=0
pointer to RECORDs or pointer-based COMMONs Common /@a/ x,y@a='f000'xy=0

where all except EXTERNAL may be local, global, formal arguments, or elements of COMMONs or RECORDs. Note that formal arguments are pointer-based by default, without specifying the '@' in the declaration. This list excludes array elements and, of course, constants and expressions. - The second EXTERNAL example deals with the RTF equivalent of Pascal IMPORT variables; see chapter 2.4.8.

2.7.3 RECORDs and pointer-based COMMON blocks

Please refer to the complete description found in chapters 2.4.5, 12-13.

2.7.4 Dynamic storage allocation

Memory may be requested dynamically as required at run-time from the stack or from a pool maintained by an operating system. RTF offers in its syntax the ALLOCATE..ENDBLOCK construct to deal with the stack. The run-time library e.g. for OS-9 offers the entry point MemAll to obtain free memory. In both cases, the object mapped onto the new piece of memory must be pointer-based.

Example:

Using the stack:
      Real @BigOne(100,1000)
      ...
      Allocate 400000 for BigOne
        BigOne(1,1)=0
        ...
      Endblock
Using free memory from system:
      Real @BigOne(100,1000)
      ...
      @BigOne=MemAll(400000)
        BigOne(1,1)=0
        ...
      Call MemRel(BigOne,400000)

2.7.5 EQUIVALENCE with formal arguments

Please refer to the complete description found in chapter 2.4.7.

2.7.6 Dynamic equivalence with ASSIGN

Please refer to the complete description found in chapter 2.6.3.

2.7.7 How to use registers

Explicit access to processor registers is possible in RTF in order to allow efficient access to often-used variables and pointers, and in order to interface with operating systems. The 68K family data registers D0-D7, address registers A0-A7, and floating point MC68881/2 coprocessor registers F0-F7 are accessible, as well as the status register SR. Integer variables can be held in the D0-D7, pointers in A0-A7, and floating point variables in F0-F7. The status register is for system programming applications only; access is restricted to supervisor state. Note that the compiler uses the registers from index 0 upwards implicitely; thus explicit use of registers should start from D7 or F7 downwards and from A4 downwards (A7-A5 used for system purposes). A warning is given in case registers are doubly used for implicit allocation by the compiler and explicit allocation by the user.

Registers are made accessible by a special form of EQUIVALENCE; see chapter 2.4.7. Note that registers usually need to be saved and restored on entry and exit of a routine; see chapter 2.5.8 for the KEEP directive.

2.7.8 Autoincrement/decrement addressing

For pointer-based vectors where the pointer resides in an address register, a specially fast access to vector elements with automatic index increment or decrement is available. This is due to the postincrement / predecrement addressing modes of the 68k family. Note that the first two arguments of a routine are automatically referenced via address registers. An example of fast code is thus the following vector differentiation:
      Subroutine VDiff(A,B,N)
      Integer A(1),B(1),N
      Integer I; Equivalence (I,D7); Keep D7
      Do I=1,N
        A(+)=B(+)-B                    ! i.e. B(i)-B(i+1)
      Enddo
      End
This works because the (+) acts as post-increment. B-B(+) is the wrong way around and gives always zero. Using one array more than once in the same statement, including one or more autoincrement/decrement accesses is too tricky to be really recommended but may result in very fast code. - Equivalencing I with D7 (and saving D7!) makes the loop even faster. Another example is the floating point scalar product:
      Function Dot(A,B,N)
      Real A(1),B(1); Integer N
      Integer I; Equivalence (I,D7); Keep D7
      Real S; Equivalence (S,F7); Keep F7
      S=0
      Do I=1,N
        S=S+A(+)*B(+)
      Enddo
      Dot=S
      End
Equivalencing the accumulator S with F7 provides speed as well as the extended precision (64-bit mantissa) used internally in the MC68881/2 chip, because the partial sum leaves the chip only after the end of the loop.

2.7.9 How to use absolute addresses

If RTF is used to access registers of a piece of special hardware (e.g. an ADC module on VME) under Fortran variable names, the base address of this hardware is often known already at compile time. Pointer based objects could be used but fixing the addresses to absolute numbers does not require pointers. The alternatives are EQUIVALENCE with absolute addresses or COMMON blocks based on absolute addresses. The second case is better suited when a whole structure of registers is based at an absolute address. In both cases, readability may be improved by using a PARAMETER declaration for the absolute address. Please refer to chapters 2.4.5 and 2.4.7.

2.8 Output from the compiler

The compiler produces a list file and an assembler code output file. The list file contains for each line the line number, the statement nesting depth (zero outside program units, incremented by one for each level of program unit, DO, IF, and ALLOCATE), an indication whether declarations occured in the line, and the source text. The nesting depth helps to find begins and ends, e.g. of loops, which belong together. It is good practice to make the nesting levels visible already when typing the source file by indentations. The declaration indicator "$" serves as a warning against unintentional implicit declarations, e.g. against misspelt variables.

The exact syntax of the generated assembly code can be controlled with the option CODE=...

The assembler code file contains very readable code. If the option MIX=ON is chosen, declarations result in comment statements (beginning with "***") which give the name of the variable, its location, data type etc. This provides the information required for dumps on variablename level.

2.8.1 Sample program listing

The program has been compiled with OPTIONS LIST=ON (see next paragraph). The following is the contents of the file SINUS.LIS produced by the compiler:
 1   0  OPTIONS LIST=ON
 2   1 $      PROGRAM SINUS 
 3   1 $      PARAMETER (N=50) 
 4   1 $      INTEGER II(2) 
 5   1 $      TYPE *,'ONLY CONSOLE(0), ALSO FILE(1), ALSO VAX(3) ?' 
 6   1        ACCEPT *,MODE 
 7   1 $      TYPE *,'START !'
 8   1        II(1)=1 
 9   1        II(2)=1 
10   2        IF(BTEST(MODE,0)) 
11   1       *  OPEN(21,FILE='LOCAL::SINUS.DAT',STATUS='UNKNOWN') 
12   2        IF(BTEST(MODE,1)) 
13   1       *  OPEN(22,FILE='SINUS.TST',STATUS='NEW',CARRIAGECONTROL='LIST')
14   2 $      DO I=1,N 
15   2 $        X=RNDM(II)-0.5 
16   2 $        X2=(1.-X)**2
17   2          TYPE 1000,I,SIN(I),X,X2 
18   3          IF(BTEST(MODE,0)) WRITE(21,1000) I,SIN(I),X,X2 
19   3          IF(BTEST(MODE,1)) WRITE(22,1000) I,SIN(I),X,X2 
20   2   1000   FORMAT(I5,3F10.5) 
21   1        ENDDO 
22   1        IF(BTEST(MODE,0)) CLOSE(21) 
23   1        IF(BTEST(MODE,1)) CLOSE(22) 
24   0        END 
Total Errors   0 Warnings 0
The first column gives the source line number. The second column indicates the statement nesting level (nested DOs, IFs etc.). A '$' in the third column, if present, indicates that some declaration has been made in this line (e.g. for the new variables I, X, X2 which are undeclared so far in the lines 14-16); it serves as a sort of warning. If undeclared variables would appear on the right-hand side of expressions, an explicit WARNING was issued.

2.9 Compiler directives

Directives which control the listing, debugging, and code generation options can be given within the source file.

2.9.1 OPTIONS directive

This directive allows to select between various code generation options available in the RTF/68K compiler - regarding the syntax of the generated assembly code, the kind of floating point hardware/emulation used, the position-independence of the generated code, and debugging features. Furthermore, various listing options may be selected. Syntax:

OPTIONS option,option,... where 'option' may be any of the following separated by commas (order irrelevant, but in case of contradicting options the last one is valid):

SIZE = LONG | SHORT LONG has to be selected if the code size of the compiled module exceeds 64 kB, i.e., no PC-relative addressing posible. SHORT (default) generates always position independent code, LONG only in the case of CPU=68020/30/40.

LIST = ON | OFF | INCLUDE ON switches source-code listing on, but include files are not listed. INCLUDE lists source with include files. OFF (default) lists only errors and warnings.

FLOAT = HARD | SOFT HARD generates instructions for the MC68881/2 floating point coprocessor (default). If not available, the 68881/2 instructions can be emulated by software. SOFT uses a software package. In all cases, IEEE number format is used.

MIX = ON | OFF ON transfers the source lines and the memory allocation of the variables to the generated assembler code (as comment lines). OFF (default) generates no such comments.

CODE = M68MIL | OS9 | MPW M68MIL the syntax of M68MIL assembler or the assembler of MacUA1, and OS9 the syntax of the assembler of the OS-9 operating system. Note that 'syntax' also reflects partially the features of the native operating system. The default depends on the respective native or host system.

DEBUG = ON | OFF ON generates additional code for comfortable debugging of the program which imposes a small runtime overhead. Also, source lines starting with 'D' or 'd' are then compiled rather than taken as comment lines. OFF (default) generates plain code, and d-lines remain comment lines.

CHECK = ON | OFF ON (default) causes called routines to check the number of actual arguments they obtain as well as stack limits. OFF omits such checks which otherwise cost about 7 usec per call on a 10 MHz 68000.

COMMON = ABSOLUTE | INDIRECT ABSOLUTE (default) means that blank and labeled commons are accessed using fixed address offsets. With INDIRECT they are referenced indirectly via a pointer. - Pointer based commons are always referenced indirectly, numerical commons are always referenced absolute, regardless of the COMMON option.

LINK = ABSOLUTE | RELATIVE Unless CODE = OS9, ABSOLUTE means that absolute references to external routines are generated. RELATIVE generates relative references, i.e. modules remain position-independent even after linking. It imposes some runtime overhead. RELATIVE offers a way to overcome the size limitation for position independent code for 68000/68010.

CPU =68000 | 68008 | 68010 |
68020 | 68030 | 68040
Selects the CPU type for which code is generated. 68000/08/10 are treated identically; code generated this way runs also on the 20/30/40. In 68020/30/40 mode, additional instructions and addressing modes are utilized which speed up execution.

FB = HARD | SOFT Selects if a subset of Fastbus routines is executed by special hardware or software.

LENGTH = FULL | 72 Selects truncation of the source line input to 72 columns. The default FULL accepts all of the source.

MULDIV = SHORT | LONG Selects whether INTEGER multiply and divide are performed with full 32-bit arithmetics (default) or not. SHORT gives faster code (MULS/DIVS instructions on the 68000 instead of software emulation). For the 68020/30, this option has no effect; 32-bit instructions are always used.

SAVE = ALL | NORMAL With ALL, all variables are kept in permanent storage, i.e. they will remain valid after routine exit and new entry; NORMAL keeps the variables which are not otherwise declared on the stack, thus providing reentrancy (default).

INTSIZE = 2 | 4 Determines whether INTEGER and LOGICAL values that are not explicitely sized occupy 2 or 4 (default) bytes.

REGSAVE = NORMAL | OUTSIDE Determines whether the registers are saved by the called routine (default) or by the caller. The latter is for compatibility with some other language implementations.

NUMPAR = ON | OFF Determines whether the number of actual arguments is passed (default) to the called routines or not.

INIT = ON | OFF Determines whether the code for system dependent initialization is generated or suppressed (default).

C_CALLS = ON | OFF Determines whether calling sequences are compatible with C (default) or not. Valid only for CODE = OS9.

REGUSE = ON | OFF Determines whether A0 and A1 are used to hold the first two arguments within routines (default) or not.

NOCLR = ON | OFF Per default, the CLR instruction is used when assigning 0 to a variable. CLR does unnecessarily a read cycle in addition to writing the 0. This may be undesirable when accessing special hardware. NOCLR = ON avoids this problem.

INIDATA = ON | OFF Per default, code is generated at each entry point to initialize DATA and COMMON pointers if not yet done. This is to make the USE directive unnecessary. If desired for efficiency, this option can be switched off.

NOP = ON | OFF If ON, a NOP is generated in front of each MOVEM instruction. This serves for special cases where the 68040 requires synchronization for correct handling of bus errors.

For example,

OPTIONS LIST=OFF,SIZE=SHORT,MIX=OFF,FLOAT=HARD,CODE=OS9, DEBUG=OFF,CHECK=ON,COMMON=ABSOLUTE,LINK=ABSOLUTE, CPU=68020,FB=SOFT,LENGTH=FULL,MULDIV=LONG,SAVE=NORMAL, INTSIZE=4,REGSAVE=NORMAL,NUMPAR=ON,INIT=OFF,C_CALLS=ON, REGUSE=ON,NOCLR=OFF,NOP=OFF,INIDATA=ON
resembles the default for OS-9.

More than one OPTIONS directive may appear in a program. The directive may be given at the very beginning of the module and in front of any program unit. It may start in column 1 or 7.

2.9.2 PUBLIC directive

The PUBLIC directive controls the format of the compiled module and thus its adaptation to the operating system environment. - As stated above, RTF/68K code relies very little on an operating system. If PUBLIC is omitted, the stack and global space initialization is done by the generated module itself. If PUBLIC is given, this initialization is not done; instead, the module is then adapted to an environment with a minimum linker/loader and has dynamic linking capability (e.g. for interactive use).

Syntax:

PUBLIC entry,entry,... where 'entry' is the name of an entry point of one of the units contained in the module. A branch table is set up at the very beginning of the module pointing to these entry points.

Only one PUBLIC directive is allowed. It must either be the first directive in a module or immediately follow OPTIONS directives if they are given at the beginning. The PUBLIC block may be in an INCLUDE file. PUBLIC may start in column 1 or 7.

2.9.3 USE directive

Implementations under some operating systems (e.g. OS-9) require that all libraries used are made known to the system by the main program such that they can be properly initialized (DATA statements, etc.). This is the purpose of the USE directive. On other systems, this directive may act as a comment. In case of the compiler option INIDATA=ON (see above), USE is not necessary.

Syntax:

USE module,module,... where 'module' is the name of a program module. Typically, the module name is derived from the source file name of the module. Subroutine calls are generated to the initialization entry points of all modules stated in USE.

Only one USE directive is allowed. It is meaningful only in a file containing a main program. USE must be the first line of the file or must follow OPTIONS and PUBLIC if any of these is given.

2.10 Compilation error messages and warnings

RTF/68K gives message numbers together with message texts. Error messages are given in severe cases, warnings in cases which are not necessarily fatal. The format of the messages is as follows:
      ****** ERROR nnn IN LINE llll - LAST SYMBOL: sssss...
      ----- message text... 
      listing of source line containing the error

      **** WARNING nnn IN LINE llll - LAST SYMBOL: sssss...
      ----- message text... 
      listing of source line causing the warning
nnn is the message number which corresponds to the message text in the second line. llll is the number of the source line where the problem occured. The source symbol in question is also given; however, a symbol internal to the compiler may also show up here. When an error (not a warning) is detected, the compiler skips to the next source statement. However, due to the recursive compilation technique, recovery from errors is not always possible, and follow-up errors may be detected in subsequent statements.

After a maximum of 20 errors, the compilation quits. There is no limit on number of warnings.

The following is a table of the message numbers together with their meanings.

1: 'Internal compiler error or follow-up error'
2: 'Identifier list expected'
3: 'End of file expected'
4: 'Options list missing or illegal'
5: 'Unknown option'
6: 'Identifier expected'
7: 'END expected'
8: 'Data space too big for 68000 - use COMMON block'
9: 'Keyword misspelt'
10: 'Label doubly defined'
11: 'Error in FORMAT list'
12: 'Pointer must be address register here'
13: 'Indexing not allowed here'
14: 'All variables must be fully declared'
15: 'Variable array bounds illegal here'
16: 'Quoted string expected'
17: 'Data type specification expected'
18: 'IMPLICIT list misspelt'
19: 'This data type or size is not supported'
20: 'Data type or array bounds doubly defined'
21: 'Attempt to redeclare global variables'
22: 'Wrong size specification'
23: 'Not enough indices given for this variable'
24: 'Only five dimensions supported'
25: 'Array bounds required'
26: 'This variable cannot be EXTERNAL'
27: 'Slash or identifier expected'
28: 'Storage doubly allocated'
29: 'Parenthesis or identifier expected'
30: 'COMMON address affected only in current file'
31: '= constant expected'
32: 'Parenthesis expected'
33: 'Comma expected'
34: 'Only two EQUIVALENCE partners supported'
35: 'Illegal EQUIVALENCE partner'
36: 'Illegal formal argument'
37: 'Illegal DATA variable list'
38: 'Variable must be COMMON, SAVE, or global'
39: 'Only one variable per DATA value list supported'
40: 'Error in DATA value list'
41: 'Data type inconsistency in DATA list'
42: 'No statement after label'
43: 'Keyword used as variable name'
44: 'Illegal use of variable name'
45: 'Label expected'
46: 'Expression expected'
47: 'Illegal actual argument'
48: 'Data type inconsistency in assignment statement'
49: 'Illegal mixing of data types'
50: 'Constant too big or unsupported data type'
51: 'Unavailable index for side exit'
52: 'Control constant must be between 0 and 7'
53: '%VAL(...) or %REF(...) expected'
54: 'Direct COMMON too big - use indirect COMON'
55: 'Value transferred in single precision only'
56: 'Syntax must be: ASSIGN label/variable TO variable'
57: 'Data type must be INTEGER*4'
58: 'Running out of registers - split expression'
59: 'Syntax must be: GOTO (label,...label) [,] expr'
60: 'Data type must be INTEGER'
61: 'Syntax must be: GOTO variable [,(label,...label)]'
62: 'Syntax must be: IF (expr) ...'
63: 'IF statement expected'
64: 'END IF expected'
65: 'Executable statement expected'
66: 'Syntax must be: IF (expr) label,label,label'
67: '(logical expr) expected'
68: 'END DO expected'
69: 'Assignment to loop variable expected'
70: 'Loop terminal or step expression expected'
71: 'Syntax must be: (unit[,form][,ERR=lab][,END=lab])'
72: 'Input/output list expected'
73: 'Syntax must be: ( [UNIT=] unit, [FILE=] file ...)'
74: 'Syntax must be: ( [UNIT=] unit )'
75: 'Format specifier expected'
76: 'String expected'
77: 'ERR=label expected'
78: '(formatlist) expected'
79: 'END=label expected'
80: '= expected'
81: 'Data type must be INTEGER or CHARACTER'
82: 'Unit specifier expected'
83: 'Variable expected'
84: '=expr expected'
85: 'Logical expression expected'
86: 'Character expression expected'
87: 'Arithmetic expression expected'
88: 'Why compare constants? '
89: 'Concatenation operator // expected'
90: 'This operation is redundant'
91: '(variable) expected'
92: 'This variable is not specified so far'
93: '(expr,expr) expected'
94: 'Actual arguments list expected'
95: 'Autoincrement/decrement not allowed here'
96: 'Variable must be a pointer variable'
97: 'Integer constant expected'
98: 'Too many indices given for this variable'
99: 'Constant index expression expected'
100: '=expr expected - maybe keyword misspelt'
101: 'The generated code maybe not position-independent'
102: 'Register variables cannot be indexed'
103: 'This requires a 68881/68882 coprocessor'
104: 'Only first array element allowed here'
105: 'Array bounds variable must be INTEGER*4'
106: 'Data type inconsistency in PARAMETER statement'
107: 'You cannot expect a result in this register'
108: 'Possible overlap with user-declared register'
109: 'Arguments of in-line routine must be declared'
110: 'Character string too long - truncated'
111: 'Incorrect FASTBUS coprocessor call'
112: 'Identifier illegal for statement function'
113: 'Substring operation (expr:expr) expected'
114: 'Syntax must be: ALLOCATE expr FOR var'
115: 'END BLOCK expected'
116: 'This label is undefined'
117: 'This DO loop label points backwards'
118: 'Available only on 68020/30'
119: 'Side exits not allowed for interrupt routines'
120: 'Formal parameter re-positioned at ENTRY'
121: 'Formal parameter doubly declared'
122: 'Consistency error in tables - abort'
123: 'String or Format beyond EOL or EOF'
124: 'Error in parser table - see expert'
125: 'Label table overflow - see expert'
126: 'Declaration table overflow - see expert'
127: 'Data stack overflow - see expert'
128: 'Internal stack overflow - see expert'
The table and stack overflows (errors 125-128) are usually due to insufficient dynamic memory in OS-9. Repeat the compilation with more memory available before contacting expert.